graphviz-2999.20.2.0/Data/0000755000000000000000000000000014535166704013112 5ustar0000000000000000graphviz-2999.20.2.0/Data/GraphViz/0000755000000000000000000000000014535166704014644 5ustar0000000000000000graphviz-2999.20.2.0/Data/GraphViz/Algorithms/0000755000000000000000000000000014535166704016755 5ustar0000000000000000graphviz-2999.20.2.0/Data/GraphViz/Attributes/0000755000000000000000000000000014535166704016772 5ustar0000000000000000graphviz-2999.20.2.0/Data/GraphViz/Attributes/Colors/0000755000000000000000000000000014535166704020233 5ustar0000000000000000graphviz-2999.20.2.0/Data/GraphViz/Commands/0000755000000000000000000000000014535166704016405 5ustar0000000000000000graphviz-2999.20.2.0/Data/GraphViz/Internal/0000755000000000000000000000000014535166704016420 5ustar0000000000000000graphviz-2999.20.2.0/Data/GraphViz/Types/0000755000000000000000000000000014535166704015750 5ustar0000000000000000graphviz-2999.20.2.0/Data/GraphViz/Types/Internal/0000755000000000000000000000000014535166704017524 5ustar0000000000000000graphviz-2999.20.2.0/tests/0000755000000000000000000000000014535166704013403 5ustar0000000000000000graphviz-2999.20.2.0/tests/Data/0000755000000000000000000000000014535166704014254 5ustar0000000000000000graphviz-2999.20.2.0/tests/Data/GraphViz/0000755000000000000000000000000014535166704016006 5ustar0000000000000000graphviz-2999.20.2.0/tests/Data/GraphViz/Attributes/0000755000000000000000000000000014535166704020134 5ustar0000000000000000graphviz-2999.20.2.0/tests/Data/GraphViz/Testing/0000755000000000000000000000000014535166704017423 5ustar0000000000000000graphviz-2999.20.2.0/tests/Data/GraphViz/Testing/Instances/0000755000000000000000000000000014535166704021352 5ustar0000000000000000graphviz-2999.20.2.0/tests/Data/GraphViz/Types/0000755000000000000000000000000014535166704017112 5ustar0000000000000000graphviz-2999.20.2.0/utils/0000755000000000000000000000000014535166704013401 5ustar0000000000000000graphviz-2999.20.2.0/Data/GraphViz.hs0000644000000000000000000005175014535166704015210 0ustar0000000000000000{-# LANGUAGE CPP, FlexibleContexts, MultiParamTypeClasses, OverloadedStrings #-} {- | Module : Data.GraphViz Description : Graphviz bindings for Haskell. Copyright : (c) Matthew Sackman, Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This is the top-level module for the graphviz library. It provides functions to convert 'Data.Graph.Inductive.Graph.Graph's into the /Dot/ language used by the /Graphviz/ suite of programs (as well as a limited ability to perform the reverse operation). If you wish to construct a Haskell representation of a Dot graph yourself rather than using the conversion functions here, please see the "Data.GraphViz.Types" module as a starting point for how to do so. Information about Graphviz and the Dot language can be found at: -} module Data.GraphViz ( -- * Conversion from graphs to /Dot/ format. -- ** Specifying parameters. -- $params GraphvizParams(..) , quickParams , defaultParams , nonClusteredParams , blankParams , setDirectedness -- *** Specifying clusters. , NodeCluster(..) , LNodeCluster -- ** Converting graphs. , graphToDot , graphElemsToDot -- ** Pseudo-inverse conversion. , dotToGraph -- * Graph augmentation. -- $augment -- ** Type aliases for @Node@ and @Edge@ labels. , AttributeNode , AttributeEdge -- ** Customisable augmentation. , graphToGraph -- ** Quick augmentation. , dotizeGraph -- ** Manual augmentation. -- $manualAugment , EdgeID , addEdgeIDs , setEdgeIDAttribute , dotAttributes , augmentGraph -- * Utility functions , preview -- * Re-exporting other modules. , module Data.GraphViz.Types , module Data.GraphViz.Types.Canonical , module Data.GraphViz.Attributes , module Data.GraphViz.Commands ) where import Data.GraphViz.Algorithms.Clustering import Data.GraphViz.Attributes import Data.GraphViz.Attributes.Complete (AttributeName, CustomAttribute, customAttribute, customValue, findSpecifiedCustom) import Data.GraphViz.Commands import Data.GraphViz.Commands.IO (hGetDot) import Data.GraphViz.Internal.Util (uniq, uniqBy) import Data.GraphViz.Types import Data.GraphViz.Types.Canonical (DotGraph (..), DotStatements (..), DotSubGraph (..)) import Data.GraphViz.Types.Generalised (FromGeneralisedDot (..)) import Control.Arrow (first, (&&&)) import Control.Concurrent (forkIO) import Data.Graph.Inductive.Graph import qualified Data.Map as Map import Data.Maybe (fromJust, mapMaybe) import qualified Data.Set as Set import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T import System.IO.Unsafe (unsafePerformIO) #if !(MIN_VERSION_base (4,8,0)) import Data.Functor ((<$>)) #endif -- ----------------------------------------------------------------------------- -- | Determine if the given graph is undirected. isUndirected :: (Ord b, Graph g) => g a b -> Bool isUndirected g = all hasFlip es where es = labEdges g eSet = Set.fromList es hasFlip e = Set.member (flippedEdge e) eSet flippedEdge (f,t,l) = (t,f,l) -- ----------------------------------------------------------------------------- {- $params A 'GraphvizParams' value contains all the information necessary to manipulate 'Graph's with this library. As such, its components deal with: * Whether to treat graphs as being directed or not; * Which top-level 'GlobalAttributes' values should be applied; * How to define (and name) clusters; * How to format clusters, nodes and edges. Apart from not having to pass multiple values around, another advantage of using 'GraphvizParams' over the previous approach is that there is no distinction between clustering and non-clustering variants of the same functions. Example usages of 'GraphvizParams' follow: * Quickly visualise a graph using the default parameters. Note the usage of @'nonClusteredParams'@ over @'defaultParams'@ to avoid type-checking problems with the cluster type. > defaultVis :: (Graph gr) => gr nl el -> DotGraph Node > defaultVis = graphToDot nonClusteredParams * As with @defaultVis@, but determine whether or not the graph is directed or undirected. > checkDirectednessVis :: (Graph gr, Ord el) => gr nl el -> DotGraph Node > checkDirectednessVis = setDirectedness graphToDot nonClusteredParams * Clustering nodes based upon whether they are even or odd. We have the option of either constructing a @GraphvizParams@ directly, or using @'blankParams'@. Using the latter to avoid setting @'isDirected'@: > evenOdd :: (Graph gr, Ord el) => gr Int el -> DotGraph Node > evenOdd = setDirectedness graphToDot params > where > params = blankParams { globalAttributes = [] > , clusterBy = clustBy > , clusterID = Num . Int > , fmtCluster = clFmt > , fmtNode = const [] > , fmtEdge = const [] > } > clustBy (n,l) = C (n `mod` 2) $ N (n,l) > clFmt m = [GraphAttrs [toLabel $ "n == " ++ show m ++ " (mod 2)"]] For more examples, see the source of 'dotizeGraph' and 'preview'. -} -- | Defines the parameters used to convert a 'Graph' into a 'DotRepr'. -- -- A value of type @'GraphvizParams' n nl el cl l@ indicates that -- the 'Graph' has a node type of @n@, node labels of type @nl@, -- edge labels of type @el@, corresponding clusters of type @cl@ and -- after clustering the nodes have a label of type @l@ (which may or -- may not be the same as @nl@). -- -- The tuples in the function types represent labelled nodes (for -- @(n,nl)@ and @(n,l)@) and labelled edges (@(n,n,el)@; the value -- @(f,t,ftl)@ is an edge from @f@ to @l@ with a label of @ftl@). -- These correspond to 'LNode' and 'LEdge' in FGL graphs. -- -- The clustering in 'clusterBy' can be to arbitrary depth. -- -- Note that the term \"cluster\" is slightly conflated here: in -- terms of @GraphvizParams@ values, a cluster is a grouping of -- nodes; the 'isDotCluster' function lets you specify whether it is -- a cluster in the Dot sense or just a sub-graph. data GraphvizParams n nl el cl l = Params { -- | @True@ if the graph is directed; @False@ -- otherwise. isDirected :: Bool -- | The top-level global 'Attributes' for the entire -- graph. , globalAttributes :: [GlobalAttributes] -- | A function to specify which cluster a particular -- node is in. , clusterBy :: ((n,nl) -> NodeCluster cl (n,l)) -- | Is this \"cluster\" actually a cluster, or just a -- sub-graph? , isDotCluster :: (cl -> Bool) -- | The name/identifier for a cluster. , clusterID :: (cl -> GraphID) -- | Specify which global attributes are applied in -- the given cluster. , fmtCluster :: (cl -> [GlobalAttributes]) -- | The specific @Attributes@ for a node. , fmtNode :: ((n,l) -> Attributes) -- | The specific @Attributes@ for an edge. , fmtEdge :: ((n,n,el) -> Attributes) } -- | An alias for 'NodeCluster' when dealing with FGL graphs. type LNodeCluster cl l = NodeCluster cl (Node,l) -- | Especially useful for quick explorations in ghci, this is a "do -- what I mean" set of parameters that prints the specified labels -- of a non-clustered graph. quickParams :: (Labellable nl, Labellable el) => GraphvizParams n nl el () nl quickParams = nonClusteredParams { fmtNode = nodeFmt, fmtEdge = edgeFmt } where nodeFmt (_,l) = [toLabel l] edgeFmt (_,_,l) = [toLabel l] -- | A default 'GraphvizParams' value which assumes the graph is -- directed, contains no clusters and has no 'Attribute's set. -- -- If you wish to have the labels of the nodes to have a different -- type after applying 'clusterBy' from before clustering, then you -- will have to specify your own 'GraphvizParams' value from -- scratch (or use 'blankParams'). -- -- If you use a custom 'clusterBy' function (which if you actually -- want clusters you should) then you should also override the -- (nonsensical) default 'clusterID'. defaultParams :: GraphvizParams n nl el cl nl defaultParams = Params { isDirected = True , globalAttributes = [] , clusterBy = N , isDotCluster = const True , clusterID = const (Num $ Int 0) , fmtCluster = const [] , fmtNode = const [] , fmtEdge = const [] } -- | A variant of 'defaultParams' that enforces that the clustering -- type is @'()'@ (i.e.: no clustering); this avoids problems when -- using 'defaultParams' internally within a function without any -- constraint on what the clustering type is. nonClusteredParams :: GraphvizParams n nl el () nl nonClusteredParams = defaultParams -- | A 'GraphvizParams' value where every field is set to -- @'undefined'@. This is useful when you have a function that will -- set some of the values for you (e.g. 'setDirectedness') but you -- don't want to bother thinking of default values to set in the -- meantime. This is especially useful when you are -- programmatically setting the clustering function (and as such do -- not know what the types might be). blankParams :: GraphvizParams n nl el cl l blankParams = Params { isDirected = error "Unspecified definition of isDirected" , globalAttributes = error "Unspecified definition of globalAttributes" , clusterBy = error "Unspecified definition of clusterBy" , isDotCluster = error "Unspecified definition of isDotCluster" , clusterID = error "Unspecified definition of clusterID" , fmtCluster = error "Unspecified definition of fmtCluster" , fmtNode = error "Unspecified definition of fmtNode" , fmtEdge = error "Unspecified definition of fmtEdge" } -- | Determine if the provided 'Graph' is directed or not and set the -- value of 'isDirected' appropriately. setDirectedness :: (Ord el, Graph gr) => (GraphvizParams Node nl el cl l -> gr nl el -> a) -> GraphvizParams Node nl el cl l -> gr nl el -> a setDirectedness f params gr = f params' gr where params' = params { isDirected = not $ isUndirected gr } -- | Convert a graph to /Dot/ format, using the specified parameters -- to cluster the graph, etc. graphToDot :: (Ord cl, Graph gr) => GraphvizParams Node nl el cl l -> gr nl el -> DotGraph Node graphToDot params graph = graphElemsToDot params (labNodes graph) (labEdges graph) -- | As with 'graphToDot', but this allows you to easily convert other -- graph-like formats to a Dot graph as long as you can get a list -- of nodes and edges from it. graphElemsToDot :: (Ord cl, Ord n) => GraphvizParams n nl el cl l -> [(n,nl)] -> [(n,n,el)] -> DotGraph n graphElemsToDot params lns les = DotGraph { strictGraph = False , directedGraph = dirGraph , graphID = Nothing , graphStatements = stmts } where dirGraph = isDirected params stmts = DotStmts { attrStmts = globalAttributes params , subGraphs = cs , nodeStmts = ns , edgeStmts = es } (cs, ns) = clustersToNodes (clusterBy params) (isDotCluster params) (clusterID params) (fmtCluster params) (fmtNode params) lns es = mapMaybe mkDotEdge les mkDotEdge e@(f,t,_) = if dirGraph || f <= t then Just DotEdge { fromNode = f , toNode = t , edgeAttributes = fmtEdge params e } else Nothing -- | A pseudo-inverse to 'graphToDot'; \"pseudo\" in the sense that -- the original node and edge labels aren't able to be -- reconstructed. dotToGraph :: (DotRepr dg Node, Graph gr) => dg Node -> gr Attributes Attributes dotToGraph dg = mkGraph ns' es where d = graphIsDirected dg -- Applying uniqBy just in case... ns = uniqBy fst . map toLN $ graphNodes dg es = concatMap toLE $ graphEdges dg -- Need to check that for some reason there aren't node IDs in an -- edge but not on their own. nSet = Set.fromList $ map fst ns nEs = map (flip (,) []) . uniq . filter (`Set.notMember` nSet) $ concatMap (\(n1,n2,_) -> [n1,n2]) es ns' = ns ++ nEs -- Conversion functions toLN (DotNode n as) = (n,as) toLE (DotEdge f t as) = (if d then id else (:) (t,f,as)) [(f,t,as)] -- ----------------------------------------------------------------------------- {- $augment The following functions provide support for passing a 'Graph' through the appropriate 'GraphvizCommand' to augment the 'Graph' by adding positional information, etc. A 'CustomAttribute' is used to distinguish multiple edges between two nodes from each other. Note that the reason that most of these functions do not have 'unsafePerformIO' applied to them is because if you set a global 'Attribute' of: @ 'Start' ('StartStyle' 'RandomStyle') @ then it will not necessarily be referentially transparent (ideally, no matter what the seed is, it will still eventually be drawn to the same optimum, but this can't be guaranteed). As such, if you are sure that you're not using such an 'Attribute', then you should be able to use 'unsafePerformIO' directly in your own code. -} -- | Augment the current node label type with the 'Attributes' applied -- to that node. type AttributeNode nl = (Attributes, nl) -- | Augment the current edge label type with the 'Attributes' applied -- to that edge. type AttributeEdge el = (Attributes, el) -- | Run the appropriate Graphviz command on the graph to get -- positional information and then combine that information back -- into the original graph. graphToGraph :: (Ord cl, Graph gr) => GraphvizParams Node nl el cl l -> gr nl el -> IO (gr (AttributeNode nl) (AttributeEdge el)) graphToGraph params gr = dotAttributes (isDirected params) gr' dot where dot = graphToDot params' gr' params' = params { fmtEdge = setEdgeIDAttribute $ fmtEdge params } gr' = addEdgeIDs gr -- ----------------------------------------------------------------------------- -- | This is a \"quick-and-dirty\" graph augmentation function that -- sets no 'Attributes' and thus should be referentially transparent -- and is wrapped in 'unsafePerformIO'. -- -- Note that the provided 'GraphvizParams' is only used for -- 'isDirected', 'clusterBy' and 'clusterID'. dotizeGraph :: (Ord cl, Graph gr) => GraphvizParams Node nl el cl l -> gr nl el -> gr (AttributeNode nl) (AttributeEdge el) dotizeGraph params gr = unsafePerformIO $ graphToGraph params' gr where params' = params { fmtCluster = const [] , fmtNode = const [] , fmtEdge = const [] } -- ----------------------------------------------------------------------------- {- $manualAugment This section allows you to manually augment graphs by providing fine-grained control over the augmentation process (the standard augmentation functions compose these together). Possible reasons for manual augmentation are: * Gain access to the intermediary 'DotRepr' used. * Convert the default 'DotGraph' to a @GDotGraph@ (found in "Data.GraphViz.Types.Generalised") so as to have greater control over the generated Dot code. * Use a specific 'GraphvizCommand' rather than the default. Note that whilst these functions provide you with more control, you must be careful how you use them: if you use the wrong 'DotRepr' for a 'Graph', then the behaviour of 'augmentGraph' (and all functions that use it) is undefined. The main point is to make sure that the defined 'DotNode' and 'DotEdge' values aren't removed (or their ID values - or the 'Attributes' for the 'DotEdge's - altered) to ensure that it is possible to match up the nodes and edges in the 'Graph' with those in the 'DotRepr'. -} -- | Used to augment an edge label with a unique identifier. data EdgeID el = EID { eID :: Text , eLbl :: el } deriving (Eq, Ord, Show) -- Show is only provided for printing/debugging purposes when using a -- normal Tree-based graph. Since it doesn't support Read, neither -- does EdgeID. -- | Add unique edge identifiers to each label. This is useful for -- when multiple edges between two nodes need to be distinguished. addEdgeIDs :: (Graph gr) => gr nl el -> gr nl (EdgeID el) addEdgeIDs g = mkGraph ns es' where ns = labNodes g es = labEdges g es' = zipWith addID es ([1..] :: [Int]) addID (f,t,l) i = (f,t,EID (T.pack $ show i) l) -- | Add a custom attribute to the list of attributes containing the -- value of the unique edge identifier. setEdgeIDAttribute :: (LEdge el -> Attributes) -> (LEdge (EdgeID el) -> Attributes) setEdgeIDAttribute f = \ e@(_,_,eid) -> identifierAttribute (eID eid) : (f . stripID) e identifierAttrName :: AttributeName identifierAttrName = "graphviz_distinguish_multiple_edges" identifierAttribute :: Text -> CustomAttribute identifierAttribute = customAttribute identifierAttrName -- | Remove the unique identifier from the 'LEdge'. stripID :: LEdge (EdgeID el) -> LEdge el stripID (f,t,eid) = (f,t, eLbl eid) -- | Pass the 'DotRepr' through the relevant command and then augment -- the 'Graph' that it came from. dotAttributes :: (Graph gr, PPDotRepr dg Node, FromGeneralisedDot dg Node) => Bool -> gr nl (EdgeID el) -> dg Node -> IO (gr (AttributeNode nl) (AttributeEdge el)) dotAttributes isDir gr dot = augmentGraph gr . parseDG <$> graphvizWithHandle command dot DotOutput hGetDot where parseDG = (`asTypeOf` dot) . fromGeneralised command = if isDir then dirCommand else undirCommand -- | Use the 'Attributes' in the provided 'DotGraph' to augment the -- node and edge labels in the provided 'Graph'. The unique -- identifiers on the edges are also stripped off. -- -- Please note that the behaviour for this function is undefined if -- the 'DotGraph' does not come from the original 'Graph' (either -- by using a conversion function or by passing the result of a -- conversion function through a 'GraphvizCommand' via the -- 'DotOutput' or similar). augmentGraph :: (Graph gr, DotRepr dg Node) => gr nl (EdgeID el) -> dg Node -> gr (AttributeNode nl) (AttributeEdge el) augmentGraph g dg = mkGraph lns les where lns = map (\(n, l) -> (n, (nodeMap Map.! n, l))) $ labNodes g les = map augmentEdge $ labEdges g augmentEdge (f,t,EID eid l) = (f,t, (edgeMap Map.! eid, l)) ns = graphNodes dg es = graphEdges dg nodeMap = Map.fromList $ map (nodeID &&& nodeAttributes) ns edgeMap = Map.fromList $ map edgeIDAttrs es edgeIDAttrs = first customValue . fromJust . findSpecifiedCustom identifierAttrName . edgeAttributes -- ----------------------------------------------------------------------------- -- Utility Functions -- | Quickly visualise a graph using the 'Xlib' 'GraphvizCanvas'. If -- your label types are not (and cannot) be instances of 'Labellable', -- you may wish to use 'gmap', 'nmap' or 'emap' to set them to a value -- such as @\"\"@. preview :: (Ord el, Graph gr, Labellable nl, Labellable el) => gr nl el -> IO () preview g = ign $ forkIO (ign $ runGraphvizCanvas' dg Xlib) where dg = setDirectedness graphToDot params g params = nonClusteredParams { fmtNode = \ (_,l) -> [toLabel l] , fmtEdge = \ (_, _, l) -> [toLabel l] } ign = (>> return ()) graphviz-2999.20.2.0/Data/GraphViz/Types.hs0000644000000000000000000004444714535166704016321 0ustar0000000000000000{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-} {- | Module : Data.GraphViz.Types Description : Haskell representation of Dot graphs. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com Four different representations of Dot graphs are available, all of which are based loosely upon the specifications at: . The 'DotRepr' class provides a common interface for them (the 'PrintDotRepr', 'ParseDotRepr' and 'PPDotRepr' classes are used until class aliases are implemented). Every representation takes in a type parameter: this indicates the node type (e.g. @DotGraph Int@ is a Dot graph with integer nodes). Sum types are allowed, though care must be taken when specifying their 'ParseDot' instances if there is the possibility of overlapping definitions. The 'GraphID' type is an existing sum type that allows textual and numeric values. If you require using more than one Dot representation, you will most likely need to import at least one of them qualified, as they typically all use the same names. As a comparison, all four representations provide how you would define the following Dot graph (or at least one isomorphic to it) (the original of which can be found at ). Note that in all the examples, they are not necessarily done the best way (variables rather than repeated constants, etc.); they are just there to provide a comparison on the structure of each representation. > digraph G { > > subgraph cluster_0 { > style=filled; > color=lightgrey; > node [style=filled,color=white]; > a0 -> a1 -> a2 -> a3; > label = "process #1"; > } > > subgraph cluster_1 { > node [style=filled]; > b0 -> b1 -> b2 -> b3; > label = "process #2"; > color=blue > } > start -> a0; > start -> b0; > a1 -> b3; > b2 -> a3; > a3 -> a0; > a3 -> end; > b3 -> end; > > start [shape=Mdiamond]; > end [shape=Msquare]; > } Each representation is suited for different things: ["Data.GraphViz.Types.Canonical"] is ideal for converting other graph-like data structures into Dot graphs (the "Data.GraphViz" module provides some functions for this). It is a structured representation of Dot code. ["Data.GraphViz.Types.Generalised"] matches the actual structure of Dot code. As such, it is suited for parsing in existing Dot code. ["Data.GraphViz.Types.Graph"] provides graph operations for manipulating Dot graphs; this is suited when you want to edit existing Dot code. It uses generalised Dot graphs for parsing and canonical Dot graphs for printing. ["Data.GraphViz.Types.Monadic"] is a much easier representation to use when defining relatively static Dot graphs in Haskell code, and looks vaguely like actual Dot code if you squint a bit. Please also read the limitations section at the end for advice on how to properly use these Dot representations. -} module Data.GraphViz.Types ( DotRepr(..) , PrintDot(..) , ParseDot(..) , PrintDotRepr , ParseDotRepr , PPDotRepr -- * Common sub-types , GraphID(..) , Number (..) , ToGraphID(..) , textGraphID , GlobalAttributes(..) , DotNode(..) , DotEdge(..) -- * Helper types for looking up information within a @DotRepr@. , ClusterLookup , NodeLookup , Path , graphStructureInformationClean , nodeInformationClean , edgeInformationClean -- * Obtaining the @DotNode@s and @DotEdges@. , graphNodes , graphEdges -- * Printing and parsing a @DotRepr@. , printDotGraph , parseDotGraph , parseDotGraphLiberally -- * Limitations and documentation -- $limitations ) where import Data.GraphViz.Attributes.Complete (rmUnwantedAttributes, usedByClusters, usedByEdges, usedByGraphs, usedByNodes) import Data.GraphViz.Internal.State (GraphvizState) import Data.GraphViz.Internal.Util (bool) import Data.GraphViz.Parsing (ParseDot(..), adjustErr, checkValidParseWithRest, parse, parseLiberally, runParserWith) import Data.GraphViz.PreProcessing (preProcess) import Data.GraphViz.Printing (PrintDot(..), printIt) import Data.GraphViz.Types.Canonical (DotGraph(..), DotStatements(..), DotSubGraph(..)) import Data.GraphViz.Types.Internal.Common (DotEdge(..), DotNode(..), GlobalAttributes(..), GraphID(..), Number(..), numericValue, withGlob) import Data.GraphViz.Types.State import Control.Arrow (second, (***)) import Control.Monad.State (evalState, execState, get, modify, put) import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T -- ----------------------------------------------------------------------------- -- | This class is used to provide a common interface to different -- ways of representing a graph in /Dot/ form. -- -- You will most probably /not/ need to create your own instances of -- this class. -- -- The type variable represents the current node type of the Dot -- graph, and the 'Ord' restriction is there because in practice -- most implementations of some of these methods require it. class (Ord n) => DotRepr dg n where -- | Convert from a graph in canonical form. This is especially -- useful when using the functions from "Data.GraphViz.Algorithms". -- -- See @FromGeneralisedDot@ in "Data.GraphViz.Types.Generalised" -- for a semi-inverse of this function. fromCanonical :: DotGraph n -> dg n -- | Return the ID of the graph. getID :: dg n -> Maybe GraphID -- | Set the ID of the graph. setID :: GraphID -> dg n -> dg n -- | Is this graph directed? graphIsDirected :: dg n -> Bool -- | Set whether a graph is directed or not. setIsDirected :: Bool -> dg n -> dg n -- | Is this graph strict? Strict graphs disallow multiple edges. graphIsStrict :: dg n -> Bool -- | A strict graph disallows multiple edges. setStrictness :: Bool -> dg n -> dg n -- | Change the node values. This function is assumed to be -- /injective/, otherwise the resulting graph will not be -- identical to the original (modulo labels). mapDotGraph :: (DotRepr dg n') => (n -> n') -> dg n -> dg n' -- | Return information on all the clusters contained within this -- 'DotRepr', as well as the top-level 'GraphAttrs' for the -- overall graph. graphStructureInformation :: dg n -> (GlobalAttributes, ClusterLookup) -- | Return information on the 'DotNode's contained within this -- 'DotRepr'. The 'Bool' parameter indicates if applicable -- 'NodeAttrs' should be included. nodeInformation :: Bool -> dg n -> NodeLookup n -- | Return information on the 'DotEdge's contained within this -- 'DotRepr'. The 'Bool' parameter indicates if applicable -- 'EdgeAttrs' should be included. edgeInformation :: Bool -> dg n -> [DotEdge n] -- | Give any anonymous sub-graphs or clusters a unique identifier -- (i.e. there will be no 'Nothing' key in the 'ClusterLookup' -- from 'graphStructureInformation'). unAnonymise :: dg n -> dg n -- | A variant of 'graphStructureInformation' with default attributes -- removed and only attributes usable by graph/cluster kept (where -- applicable). graphStructureInformationClean :: (DotRepr dg n) => dg n -> (GlobalAttributes, ClusterLookup) graphStructureInformationClean = (globOnly *** fmap (second clustOnly)) . graphStructureInformation where globOnly = withGlob $ filter usedByGraphs . rmUnwantedAttributes clustOnly = withGlob $ filter usedByClusters . rmUnwantedAttributes -- | A variant of 'nodeInformation' with default attributes removed -- and only attributes used by nodes kept. nodeInformationClean :: (DotRepr dg n) => Bool -> dg n -> NodeLookup n nodeInformationClean = (fmap (second nodeOnly) .) . nodeInformation where nodeOnly = filter usedByNodes . rmUnwantedAttributes -- | A variant of 'edgeInformation' with default attributes removed -- and only attributes used by edges kept. edgeInformationClean :: (DotRepr dg n) => Bool -> dg n -> [DotEdge n] edgeInformationClean = (map rmEdgeAs .) . edgeInformation where rmEdgeAs de = de { edgeAttributes = edgeOnly $ edgeAttributes de } edgeOnly = filter usedByEdges . rmUnwantedAttributes -- | This class exists just to make type signatures nicer; all -- instances of 'DotRepr' should also be an instance of -- 'PrintDotRepr'. class (DotRepr dg n, PrintDot (dg n)) => PrintDotRepr dg n -- | This class exists just to make type signatures nicer; all -- instances of 'DotRepr' should also be an instance of -- 'ParseDotRepr'. class (DotRepr dg n, ParseDot (dg n)) => ParseDotRepr dg n -- | This class exists just to make type signatures nicer; all -- instances of 'DotRepr' should also be an instance of -- 'PPDotRepr'. class (PrintDotRepr dg n, ParseDotRepr dg n) => PPDotRepr dg n -- | Returns all resultant 'DotNode's in the 'DotRepr' (not including -- 'NodeAttr's). graphNodes :: (DotRepr dg n) => dg n -> [DotNode n] graphNodes = toDotNodes . nodeInformation False -- | Returns all resultant 'DotEdge's in the 'DotRepr' (not including -- 'EdgeAttr's). graphEdges :: (DotRepr dg n) => dg n -> [DotEdge n] graphEdges = edgeInformation False -- | The actual /Dot/ code for an instance of 'DotRepr'. Note that it -- is expected that @'parseDotGraph' . 'printDotGraph' == 'id'@ -- (this might not be true the other way around due to un-parseable -- components). printDotGraph :: (PrintDotRepr dg n) => dg n -> Text printDotGraph = printIt -- | Parse a limited subset of the Dot language to form an instance of -- 'DotRepr'. Each instance may have its own limitations on what -- may or may not be parseable Dot code. -- -- Also removes any comments, etc. before parsing. parseDotGraph :: (ParseDotRepr dg n) => Text -> dg n parseDotGraph = parseDotGraphWith id -- | As with 'parseDotGraph', but if an 'Attribute' cannot be parsed -- strictly according to the known rules, let it fall back to being -- parsed as an 'UnknownAttribute'. This is especially useful for -- when using a version of Graphviz that is either newer (especially -- for the XDot attributes) or older (when some attributes have -- changed) but you'd still prefer it to parse rather than throwing -- an error. parseDotGraphLiberally :: (ParseDotRepr dg n) => Text -> dg n parseDotGraphLiberally = parseDotGraphWith parseLiberally parseDotGraphWith :: (ParseDotRepr dg n) => (GraphvizState -> GraphvizState) -> Text -> dg n parseDotGraphWith f = prs . preProcess where prs = checkValidParseWithRest . runParserWith f parse' parse' = parse `adjustErr` ("Unable to parse the Dot graph; usually this is because of either:\n\ \ * Wrong choice of representation: try the Generalised one\n\ \ * Wrong choice of node type; try with `DotGraph String`.\n\ \\n\ \The actual parsing error was:\n\t"++) -- ----------------------------------------------------------------------------- -- Instance for Canonical graphs, to avoid cyclic modules. instance (Ord n) => DotRepr DotGraph n where fromCanonical = id getID = graphID setID i g = g { graphID = Just i } graphIsDirected = directedGraph setIsDirected d g = g { directedGraph = d } graphIsStrict = strictGraph setStrictness s g = g { strictGraph = s } mapDotGraph = fmap graphStructureInformation = getGraphInfo . statementStructure . graphStatements nodeInformation wGlobal = getNodeLookup wGlobal . statementNodes . graphStatements edgeInformation wGlobal = getDotEdges wGlobal . statementEdges . graphStatements unAnonymise = renumber instance (Ord n, PrintDot n) => PrintDotRepr DotGraph n instance (Ord n, ParseDot n) => ParseDotRepr DotGraph n instance (Ord n, PrintDot n, ParseDot n) => PPDotRepr DotGraph n statementStructure :: DotStatements n -> GraphState () statementStructure stmts = do mapM_ addGraphGlobals $ attrStmts stmts mapM_ (withSubGraphID addSubGraph statementStructure) $ subGraphs stmts statementNodes :: (Ord n) => DotStatements n -> NodeState n () statementNodes stmts = do mapM_ addNodeGlobals $ attrStmts stmts mapM_ (withSubGraphID recursiveCall statementNodes) $ subGraphs stmts mapM_ addNode $ nodeStmts stmts mapM_ addEdgeNodes $ edgeStmts stmts statementEdges :: DotStatements n -> EdgeState n () statementEdges stmts = do mapM_ addEdgeGlobals $ attrStmts stmts mapM_ (withSubGraphID recursiveCall statementEdges) $ subGraphs stmts mapM_ addEdge $ edgeStmts stmts withSubGraphID :: (Maybe (Maybe GraphID) -> b -> a) -> (DotStatements n -> b) -> DotSubGraph n -> a withSubGraphID f g sg = f mid . g $ subGraphStmts sg where mid = bool Nothing (Just $ subGraphID sg) $ isCluster sg renumber :: DotGraph n -> DotGraph n renumber dg = dg { graphStatements = newStmts } where startN = succ $ maxSGInt dg newStmts = evalState (stRe $ graphStatements dg) startN stRe st = do sgs' <- mapM sgRe $ subGraphs st return $ st { subGraphs = sgs' } sgRe sg = do sgid' <- case subGraphID sg of Nothing -> do n <- get put $ succ n return . Just . Num $ Int n sgid -> return sgid stmts' <- stRe $ subGraphStmts sg return $ sg { subGraphID = sgid' , subGraphStmts = stmts' } maxSGInt :: DotGraph n -> Int maxSGInt dg = execState (stInt $ graphStatements dg) . (`check` 0) $ graphID dg where check = maybe id max . (numericValue =<<) stInt = mapM_ sgInt . subGraphs sgInt sg = do modify (check $ subGraphID sg) stInt $ subGraphStmts sg -- ----------------------------------------------------------------------------- -- | A convenience class to make it easier to convert data types to -- 'GraphID' values, e.g. for cluster identifiers. -- -- In most cases, conversion would be via the 'Text' or 'String' -- instances (e.g. using 'show'). class ToGraphID a where toGraphID :: a -> GraphID -- | An alias for 'toGraphID' for use with the @OverloadedStrings@ -- extension. textGraphID :: Text -> GraphID textGraphID = toGraphID instance ToGraphID Text where toGraphID = Str instance ToGraphID String where toGraphID = toGraphID . T.pack instance ToGraphID Char where toGraphID = toGraphID . T.singleton instance ToGraphID Int where toGraphID = Num . Int -- | This instance loses precision by going via 'Int'. instance ToGraphID Integer where toGraphID = Num . Int . fromInteger instance ToGraphID Double where toGraphID = Num . Dbl -- ----------------------------------------------------------------------------- {- $limitations Printing of /Dot/ code is done as strictly as possible, whilst parsing is as permissive as possible. For example, if the types allow it then @\"2\"@ will be parsed as an 'Int' value. Note that quoting and escaping of textual values is done automagically. A summary of known limitations\/differences: * When creating 'GraphID' values for graphs and sub-graphs, you should ensure that none of them have the same printed value as one of the node identifiers values to avoid any possible problems. * If you want any 'GlobalAttributes' in a sub-graph and want them to only apply to that sub-graph, then you must ensure it does indeed have a valid 'GraphID'. * All sub-graphs which represent clusters should have unique identifiers (well, only if you want them to be generated sensibly). * If eventually outputting to a format such as SVG, then you should make sure to specify an identifier for the overall graph, as that is used as the title of the resulting image. * Whilst the graphs, etc. are polymorphic in their node type, you should ensure that you use a relatively simple node type (that is, it only covers a single line, etc.). * Also, whilst Graphviz allows you to mix the types used for nodes, this library requires\/assumes that they are all the same type (but you /can/ use a sum-type). * 'DotEdge' defines an edge @(a, b)@ (with an edge going from @a@ to @b@); in /Dot/ parlance the edge has a head at @a@ and a tail at @b@. Care must be taken when using the related @Head*@ and @Tail*@ 'Attribute's. See the differences section in "Data.GraphViz.Attributes" for more information. * It is common to see multiple edges defined on the one line in Dot (e.g. @n1 -> n2 -> n3@ means to create a directed edge from @n1@ to @n2@ and from @n2@ to @n3@). These types of edge definitions are parseable; however, they are converted to singleton edges. * It is not yet possible to create or parse edges with subgraphs\/clusters as one of the end points. * The parser will strip out comments and pre-processor lines, join together multiline statements and concatenate split strings together. However, pre-processing within HTML-like labels is currently not supported. * Graphviz allows a node to be \"defined\" twice (e.g. the actual node definition, and then in a subgraph with extra global attributes applied to it). This actually represents the same node, but when parsing they will be considered as separate 'DotNode's (such that 'graphNodes' will return both \"definitions\"). @canonicalise@ from "Data.GraphViz.Algorithms" can be used to fix this. See "Data.GraphViz.Attributes.Complete" for more limitations. -} graphviz-2999.20.2.0/Data/GraphViz/Types/Canonical.hs0000644000000000000000000002327014535166704020177 0ustar0000000000000000{- | Module : Data.GraphViz.Types.Canonical Description : The canonical representation of Dot graphs. Copyright : (c) Matthew Sackman, Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com A canonical Dot graph requires that within each graph/sub-graph, the statements are in the following order: * global attributes * sub-graphs/clusters * nodes * edges This Dot graph representation is ideally suited for converting other data structures to Dot form (especially with the help of @graphElemsToDot@ from "Data.GraphViz"). If you require arbitrary ordering of statements, then use "Data.GraphViz.Types.Generalised". The sample graph could be implemented (this is actually the result of calling @canonicalise@ from "Data.GraphViz.Algorithms" on the generalised one) as: > DotGraph { strictGraph = False > , directedGraph = True > , graphID = Just (Str "G") > , graphStatements = DotStmts { attrStmts = [] > , subGraphs = [ DotSG { isCluster = True > , subGraphID = Just (Num (Int 0)) > , subGraphStmts = DotStmts { attrStmts = [ GraphAttrs [ style filled > , color LightGray > , textLabel "process #1"] > , NodeAttrs [style filled, color White]] > , subGraphs = [] > , nodeStmts = [ DotNode "a0" [] > , DotNode "a1" [] > , DotNode "a2" [] > , DotNode "a3" []] > , edgeStmts = [ DotEdge "a0" "a1" [] > , DotEdge "a1" "a2" [] > , DotEdge "a2" "a3" [] > , DotEdge "a3" "a0" []]}} > , DotSG { isCluster = True > , subGraphID = Just (Num (Int 1)) > , subGraphStmts = DotStmts { attrStmts = [ GraphAttrs [textLabel "process #2", color Blue] > , NodeAttrs [style filled]] > , subGraphs = [] > , nodeStmts = [ DotNode "b0" [] > , DotNode "b1" [] > , DotNode "b2" [] > , DotNode "b3" []] > , edgeStmts = [ DotEdge "b0" "b1" [] > , DotEdge "b1" "b2" [] > , DotEdge "b2" "b3" []]}}] > , nodeStmts = [ DotNode "end" [shape MSquare] > , DotNode "start" [shape MDiamond]] > , edgeStmts = [ DotEdge "start" "a0" [] > , DotEdge "start" "b0" [] > , DotEdge "a1" "b3" [] > , DotEdge "b2" "a3" [] > , DotEdge "a3" "end" [] > , DotEdge "b3" "end" []]}} Note that whilst the above graph represents the same Dot graph as specified in "Data.GraphViz.Types.Generalised", etc., it /may/ be drawn slightly differently by the various Graphviz tools. -} module Data.GraphViz.Types.Canonical ( DotGraph(..) -- * Sub-components of a @DotGraph@. , DotStatements(..) , DotSubGraph(..) -- * Re-exported from @Data.GraphViz.Types@ , GraphID(..) , GlobalAttributes(..) , DotNode(..) , DotEdge(..) ) where import Data.GraphViz.Internal.State (AttributeType (..)) import Data.GraphViz.Internal.Util (bool) import Data.GraphViz.Parsing import Data.GraphViz.Printing import Data.GraphViz.Types.Internal.Common import Control.Arrow ((&&&)) -- ----------------------------------------------------------------------------- -- | A Dot graph in canonical form. data DotGraph n = DotGraph { strictGraph :: Bool -- ^ If 'True', no multiple edges are drawn. , directedGraph :: Bool , graphID :: Maybe GraphID , graphStatements :: DotStatements n } deriving (Eq, Ord, Show, Read) instance (PrintDot n) => PrintDot (DotGraph n) where unqtDot = printStmtBased printGraphID' (const GraphAttribute) graphStatements toDot where printGraphID' = printGraphID strictGraph directedGraph graphID instance (ParseDot n) => ParseDot (DotGraph n) where parseUnqt = parseGraphID DotGraph <*> parseBracesBased GraphAttribute parseUnqt parse = parseUnqt -- Don't want the option of quoting -- | Assumed to be an injective mapping function. instance Functor DotGraph where fmap f g = g { graphStatements = fmap f $ graphStatements g } -- ----------------------------------------------------------------------------- data DotStatements n = DotStmts { attrStmts :: [GlobalAttributes] , subGraphs :: [DotSubGraph n] , nodeStmts :: [DotNode n] , edgeStmts :: [DotEdge n] } deriving (Eq, Ord, Show, Read) instance (PrintDot n) => PrintDot (DotStatements n) where unqtDot stmts = vcat $ sequence [ unqtDot $ attrStmts stmts , unqtDot $ subGraphs stmts , unqtDot $ nodeStmts stmts , unqtDot $ edgeStmts stmts ] instance (ParseDot n) => ParseDot (DotStatements n) where parseUnqt = do atts <- tryParseList newline' sGraphs <- tryParseList newline' nodes <- tryParseList newline' edges <- tryParseList return $ DotStmts atts sGraphs nodes edges parse = parseUnqt -- Don't want the option of quoting `adjustErr` ("Not a valid set of statements\n\t"++) instance Functor DotStatements where fmap f stmts = stmts { subGraphs = map (fmap f) $ subGraphs stmts , nodeStmts = map (fmap f) $ nodeStmts stmts , edgeStmts = map (fmap f) $ edgeStmts stmts } -- ----------------------------------------------------------------------------- data DotSubGraph n = DotSG { isCluster :: Bool , subGraphID :: Maybe GraphID , subGraphStmts :: DotStatements n } deriving (Eq, Ord, Show, Read) instance (PrintDot n) => PrintDot (DotSubGraph n) where unqtDot = printStmtBased printSubGraphID' subGraphAttrType subGraphStmts toDot unqtListToDot = printStmtBasedList printSubGraphID' subGraphAttrType subGraphStmts toDot listToDot = unqtListToDot subGraphAttrType :: DotSubGraph n -> AttributeType subGraphAttrType = bool SubGraphAttribute ClusterAttribute . isCluster printSubGraphID' :: DotSubGraph n -> DotCode printSubGraphID' = printSubGraphID (isCluster &&& subGraphID) instance (ParseDot n) => ParseDot (DotSubGraph n) where parseUnqt = parseSubGraph DotSG parseUnqt `onFail` -- Take "anonymous" DotSubGraphs into account. fmap (DotSG False Nothing) (parseBracesBased SubGraphAttribute parseUnqt) parse = parseUnqt -- Don't want the option of quoting `adjustErr` ("Not a valid Sub Graph\n\t"++) parseUnqtList = sepBy (whitespace >> parseUnqt) newline' parseList = parseUnqtList instance Functor DotSubGraph where fmap f sg = sg { subGraphStmts = fmap f $ subGraphStmts sg } graphviz-2999.20.2.0/Data/GraphViz/Types/Generalised.hs0000644000000000000000000003343614535166704020537 0ustar0000000000000000{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} {- | Module : Data.GraphViz.Types.Generalised. Description : Alternate definition of the Graphviz types. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com The generalised Dot representation most closely matches the implementation of actual Dot code, as it places no restrictions on ordering of elements, etc. As such it should be able to parse any existing Dot code (taking into account the parsing limitations/assumptions). The sample graph could be implemented (this is actually a prettied version of parsing in the Dot code) as: > DotGraph { strictGraph = False > , directedGraph = True > , graphID = Just (Str "G") > , graphStatements = Seq.fromList [ SG $ DotSG { isCluster = True > , subGraphID = Just (Int 0) > , subGraphStmts = Seq.fromList [ GA $ GraphAttrs [style filled] > , GA $ GraphAttrs [color LightGray] > , GA $ NodeAttrs [style filled, color White] > , DE $ DotEdge "a0" "a1" [] > , DE $ DotEdge "a1" "a2" [] > , DE $ DotEdge "a2" "a3" [] > , GA $ GraphAttrs [textLabel "process #1"]]} > , SG $ DotSG { isCluster = True > , subGraphID = Just (Int 1) > , subGraphStmts = fromList [ GA $ NodeAttrs [style filled] > , DE $ DotEdge "b0" "b1" [] > , DE $ DotEdge "b1" "b2" [] > , DE $ DotEdge "b2" "b3" [] > , GA $ GraphAttrs [textLabel "process #2"] > , GA $ GraphAttrs [color Blue]]} > , DE $ DotEdge "start" "a0" [] > , DE $ DotEdge "start" "b0" [] > , DE $ DotEdge "a1" "b3" [] > , DE $ DotEdge "b2" "a3" [] > , DE $ DotEdge "a3" "a0" [] > , DE $ DotEdge "a3" "end" [] > , DE $ DotEdge "b3" "end" [] > , DN $ DotNode "start" [shape MDiamond] > , DN $ DotNode "end" [shape MSquare]]} -} module Data.GraphViz.Types.Generalised ( DotGraph(..) , FromGeneralisedDot (..) -- * Sub-components of a @DotGraph@. , DotStatements , DotStatement(..) , DotSubGraph(..) -- * Re-exported from @Data.GraphViz.Types@. , GraphID(..) , GlobalAttributes(..) , DotNode(..) , DotEdge(..) ) where import Data.GraphViz.Algorithms (canonicalise) import Data.GraphViz.Internal.State (AttributeType(..)) import Data.GraphViz.Internal.Util (bool) import Data.GraphViz.Parsing import Data.GraphViz.Printing import Data.GraphViz.Types import qualified Data.GraphViz.Types.Canonical as C import Data.GraphViz.Types.Internal.Common import Data.GraphViz.Types.State import Control.Arrow ((&&&)) import Control.Monad.State (evalState, execState, get, modify, put) import qualified Data.Foldable as F import Data.Sequence (Seq, (><)) import qualified Data.Sequence as Seq import qualified Data.Traversable as T -- ----------------------------------------------------------------------------- -- | The internal representation of a generalised graph in Dot form. data DotGraph n = DotGraph { -- | If 'True', no multiple edges are drawn. strictGraph :: Bool , directedGraph :: Bool , graphID :: Maybe GraphID , graphStatements :: DotStatements n } deriving (Eq, Ord, Show, Read) instance (Ord n) => DotRepr DotGraph n where fromCanonical = generaliseDotGraph getID = graphID setID i g = g { graphID = Just i } graphIsDirected = directedGraph setIsDirected d g = g { directedGraph = d } graphIsStrict = strictGraph setStrictness s g = g { strictGraph = s } mapDotGraph = fmap graphStructureInformation = getGraphInfo . statementStructure . graphStatements nodeInformation wGlobal = getNodeLookup wGlobal . statementNodes . graphStatements edgeInformation wGlobal = getDotEdges wGlobal . statementEdges . graphStatements unAnonymise = renumber instance (Ord n, PrintDot n) => PrintDotRepr DotGraph n instance (Ord n, ParseDot n) => ParseDotRepr DotGraph n instance (Ord n, PrintDot n, ParseDot n) => PPDotRepr DotGraph n instance (PrintDot n) => PrintDot (DotGraph n) where unqtDot = printStmtBased printGraphID' (const GraphAttribute) graphStatements printGStmts where printGraphID' = printGraphID strictGraph directedGraph graphID instance (ParseDot n) => ParseDot (DotGraph n) where parseUnqt = parseGraphID DotGraph <*> parseBracesBased GraphAttribute parseGStmts parse = parseUnqt -- Don't want the option of quoting `adjustErr` ("Not a valid generalised DotGraph\n\t"++) -- | Assumed to be an injective mapping function. instance Functor DotGraph where fmap f g = g { graphStatements = (fmap . fmap) f $ graphStatements g } -- | Convert a 'DotGraph' to a 'DotGraph', keeping the same order of -- statements. generaliseDotGraph :: C.DotGraph n -> DotGraph n generaliseDotGraph dg = DotGraph { strictGraph = C.strictGraph dg , directedGraph = C.directedGraph dg , graphID = C.graphID dg , graphStatements = generaliseStatements $ C.graphStatements dg } -- ----------------------------------------------------------------------------- -- | This class is useful for being able to parse in a dot graph as a -- generalised one, and then convert it to your preferred -- representation. -- -- This can be seen as a semi-inverse of 'fromCanonical'. class (DotRepr dg n) => FromGeneralisedDot dg n where fromGeneralised :: DotGraph n -> dg n instance (Ord n) => FromGeneralisedDot C.DotGraph n where fromGeneralised = canonicalise instance (Ord n) => FromGeneralisedDot DotGraph n where fromGeneralised = id -- ----------------------------------------------------------------------------- type DotStatements n = Seq (DotStatement n) printGStmts :: (PrintDot n) => DotStatements n -> DotCode printGStmts = toDot . F.toList parseGStmts :: (ParseDot n) => Parse (DotStatements n) parseGStmts = (Seq.fromList <$> parse) `adjustErr` ("Not a valid generalised DotStatements\n\t"++) statementStructure :: DotStatements n -> GraphState () statementStructure = F.mapM_ stmtStructure statementNodes :: (Ord n) => DotStatements n -> NodeState n () statementNodes = F.mapM_ stmtNodes statementEdges :: DotStatements n -> EdgeState n () statementEdges = F.mapM_ stmtEdges generaliseStatements :: C.DotStatements n -> DotStatements n generaliseStatements stmts = atts >< sgs >< ns >< es where atts = Seq.fromList . map GA $ C.attrStmts stmts sgs = Seq.fromList . map (SG . generaliseSubGraph) $ C.subGraphs stmts ns = Seq.fromList . map DN $ C.nodeStmts stmts es = Seq.fromList . map DE $ C.edgeStmts stmts data DotStatement n = GA GlobalAttributes | SG (DotSubGraph n) | DN (DotNode n) | DE (DotEdge n) deriving (Eq, Ord, Show, Read) instance (PrintDot n) => PrintDot (DotStatement n) where unqtDot (GA ga) = unqtDot ga unqtDot (SG sg) = unqtDot sg unqtDot (DN dn) = unqtDot dn unqtDot (DE de) = unqtDot de unqtListToDot = vcat . mapM unqtDot listToDot = unqtListToDot instance (ParseDot n) => ParseDot (DotStatement n) where parseUnqt = oneOf [ GA <$> parseUnqt , SG <$> parseUnqt , DN <$> parseUnqt , DE <$> parseUnqt ] parse = parseUnqt -- Don't want the option of quoting `adjustErr` ("Not a valid statement\n\t"++) parseUnqtList = fmap concat . wrapWhitespace $ parseStatements p where -- Have to do something special here because of "a -> b -> c" -- syntax for edges. p = fmap (map DE) parseEdgeLine `onFail` fmap (:[]) parse parseList = parseUnqtList instance Functor DotStatement where fmap _ (GA ga) = GA ga -- Have to re-make this to make the type checker happy. fmap f (SG sg) = SG $ fmap f sg fmap f (DN dn) = DN $ fmap f dn fmap f (DE de) = DE $ fmap f de stmtStructure :: DotStatement n -> GraphState () stmtStructure (GA ga) = addGraphGlobals ga stmtStructure (SG sg) = withSubGraphID addSubGraph statementStructure sg stmtStructure _ = return () stmtNodes :: (Ord n) => DotStatement n -> NodeState n () stmtNodes (GA ga) = addNodeGlobals ga stmtNodes (SG sg) = withSubGraphID recursiveCall statementNodes sg stmtNodes (DN dn) = addNode dn stmtNodes (DE de) = addEdgeNodes de stmtEdges :: DotStatement n -> EdgeState n () stmtEdges (GA ga) = addEdgeGlobals ga stmtEdges (SG sg) = withSubGraphID recursiveCall statementEdges sg stmtEdges (DE de) = addEdge de stmtEdges _ = return () -- ----------------------------------------------------------------------------- data DotSubGraph n = DotSG { isCluster :: Bool , subGraphID :: Maybe GraphID , subGraphStmts :: DotStatements n } deriving (Eq, Ord, Show, Read) instance (PrintDot n) => PrintDot (DotSubGraph n) where unqtDot = printStmtBased printSubGraphID' subGraphAttrType subGraphStmts printGStmts unqtListToDot = printStmtBasedList printSubGraphID' subGraphAttrType subGraphStmts printGStmts listToDot = unqtListToDot subGraphAttrType :: DotSubGraph n -> AttributeType subGraphAttrType = bool SubGraphAttribute ClusterAttribute . isCluster printSubGraphID' :: DotSubGraph n -> DotCode printSubGraphID' = printSubGraphID (isCluster &&& subGraphID) instance (ParseDot n) => ParseDot (DotSubGraph n) where parseUnqt = parseSubGraph DotSG parseGStmts `onFail` -- Take anonymous DotSubGraphs into account fmap (DotSG False Nothing) (parseBracesBased SubGraphAttribute parseGStmts) parse = parseUnqt -- Don't want the option of quoting `adjustErr` ("Not a valid Sub Graph\n\t"++) parseUnqtList = sepBy (whitespace *> parseUnqt) newline' parseList = parseUnqtList instance Functor DotSubGraph where fmap f sg = sg { subGraphStmts = (fmap . fmap) f $ subGraphStmts sg } generaliseSubGraph :: C.DotSubGraph n -> DotSubGraph n generaliseSubGraph (C.DotSG isC mID stmts) = DotSG { isCluster = isC , subGraphID = mID , subGraphStmts = stmts' } where stmts' = generaliseStatements stmts withSubGraphID :: (Maybe (Maybe GraphID) -> b -> a) -> (DotStatements n -> b) -> DotSubGraph n -> a withSubGraphID f g sg = f mid . g $ subGraphStmts sg where mid = bool Nothing (Just $ subGraphID sg) $ isCluster sg renumber :: DotGraph n -> DotGraph n renumber dg = dg { graphStatements = newStmts } where startN = succ $ maxSGInt dg newStmts = evalState (stsRe $ graphStatements dg) startN stsRe = T.mapM stRe stRe (SG sg) = SG <$> sgRe sg stRe stmt = pure stmt sgRe sg = do sgid' <- case subGraphID sg of Nothing -> do n <- get put $ succ n return . Just . Num $ Int n sgid -> return sgid stmts' <- stsRe $ subGraphStmts sg return $ sg { subGraphID = sgid' , subGraphStmts = stmts' } maxSGInt :: DotGraph n -> Int maxSGInt dg = execState (stsInt $ graphStatements dg) . (`check` 0) $ graphID dg where check = maybe id max . (numericValue =<<) stsInt = F.mapM_ stInt stInt (SG sg) = sgInt sg stInt _ = return () sgInt sg = do modify (check $ subGraphID sg) stsInt $ subGraphStmts sg graphviz-2999.20.2.0/Data/GraphViz/Types/Graph.hs0000644000000000000000000007270214535166704017355 0ustar0000000000000000{-# LANGUAGE CPP, FlexibleInstances, MultiParamTypeClasses #-} {- | Module : Data.GraphViz.Types.Graph Description : A graph-like representation of Dot graphs. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com It is sometimes useful to be able to manipulate a Dot graph /as/ an actual graph. This representation lets you do so, using an inductive approach based upon that from FGL (note that 'DotGraph' is /not/ an instance of the FGL classes due to having the wrong kind). Note, however, that the API is not as complete as proper graph implementations. For purposes of manipulation, all edges are found in the root graph and not in a cluster; as such, having 'EdgeAttrs' in a cluster's 'GlobalAttributes' is redundant. Printing is achieved via "Data.GraphViz.Types.Canonical" (using 'toCanonical') and parsing via "Data.GraphViz.Types.Generalised" (so /any/ piece of Dot code can be parsed in). This representation doesn't allow non-cluster sub-graphs. Also, all clusters /must/ have a unique identifier. For those functions (with the exception of 'DotRepr' methods) that take or return a \"@Maybe GraphID@\", a value of \"@Nothing@\" refers to the root graph; \"@Just clust@\" refers to the cluster with the identifier \"@clust@\". You would not typically explicitly create these values, instead converting existing Dot graphs (via 'fromDotRepr'). However, one way of constructing the sample graph would be: > setID (Str "G") > . setStrictness False > . setIsDirected True > . setClusterAttributes (Int 0) [GraphAttrs [style filled, color LightGray, textLabel "process #1"], NodeAttrs [style filled, color White]] > . setClusterAttributes (Int 1) [GraphAttrs [textLabel "process #2", color Blue], NodeAttrs [style filled]] > $ composeList [ Cntxt "a0" (Just $ Int 0) [] [("a3",[]),("start",[])] [("a1",[])] > , Cntxt "a1" (Just $ Int 0) [] [] [("a2",[]),("b3",[])] > , Cntxt "a2" (Just $ Int 0) [] [] [("a3",[])] > , Cntxt "a3" (Just $ Int 0) [] [("b2",[])] [("end",[])] > , Cntxt "b0" (Just $ Int 1) [] [("start",[])] [("b1",[])] > , Cntxt "b1" (Just $ Int 1) [] [] [("b2",[])] > , Cntxt "b2" (Just $ Int 1) [] [] [("b3",[])] > , Cntxt "b3" (Just $ Int 1) [] [] [("end",[])] > , Cntxt "end" Nothing [shape MSquare] [] [] > , Cntxt "start" Nothing [shape MDiamond] [] []] -} module Data.GraphViz.Types.Graph ( DotGraph , GraphID(..) , Context(..) -- * Conversions , toCanonical , unsafeFromCanonical , fromDotRepr -- * Graph information , isEmpty , hasClusters , isEmptyGraph , graphAttributes , parentOf , clusterAttributes , foundInCluster , attributesOf , predecessorsOf , successorsOf , adjacentTo , adjacent -- * Graph construction , mkGraph , emptyGraph , (&) , composeList , addNode , DotNode(..) , addDotNode , addEdge , DotEdge(..) , addDotEdge , addCluster , setClusterParent , setClusterAttributes -- * Graph deconstruction , decompose , decomposeAny , decomposeList , deleteNode , deleteAllEdges , deleteEdge , deleteDotEdge , deleteCluster , removeEmptyClusters ) where import Data.GraphViz.Algorithms (CanonicaliseOptions(..), canonicaliseOptions) import Data.GraphViz.Algorithms.Clustering import Data.GraphViz.Attributes.Complete (Attributes) import Data.GraphViz.Attributes.Same import Data.GraphViz.Internal.Util (groupSortBy, groupSortCollectBy) import Data.GraphViz.Types import qualified Data.GraphViz.Types.Canonical as C import qualified Data.GraphViz.Types.Generalised as G import Data.GraphViz.Types.Internal.Common (partitionGlobal) import qualified Data.GraphViz.Types.State as St import Control.Applicative (liftA2, (<|>)) import Control.Arrow ((***)) import qualified Data.Foldable as F import Data.List (delete, foldl', unfoldr) import Data.Map (Map) import qualified Data.Map as M import Data.Maybe (fromMaybe, mapMaybe, maybeToList) import qualified Data.Sequence as Seq import qualified Data.Set as S import Text.ParserCombinators.ReadPrec (prec) import Text.Read (Lexeme(Ident), lexP, parens, readPrec) #if !(MIN_VERSION_base (4,8,0)) import Control.Applicative ((<$>), (<*>)) #endif -- ----------------------------------------------------------------------------- -- | A Dot graph that allows graph operations on it. data DotGraph n = DG { strictGraph :: !Bool , directedGraph :: !Bool , graphAttrs :: !GlobAttrs , graphID :: !(Maybe GraphID) , clusters :: !(Map GraphID ClusterInfo) , values :: !(NodeMap n) } deriving (Eq, Ord) -- | It should be safe to substitute 'unsafeFromCanonical' for -- 'fromCanonical' in the output of this. instance (Show n) => Show (DotGraph n) where showsPrec d dg = showParen (d > 10) $ showString "fromCanonical " . shows (toCanonical dg) -- | If the graph is the output from 'show', then it should be safe to -- substitute 'unsafeFromCanonical' for 'fromCanonical'. instance (Ord n, Read n) => Read (DotGraph n) where readPrec = parens . prec 10 $ do Ident "fromCanonical" <- lexP cdg <- readPrec return $ fromCanonical cdg data GlobAttrs = GA { graphAs :: !SAttrs , nodeAs :: !SAttrs , edgeAs :: !SAttrs } deriving (Eq, Ord, Show, Read) data NodeInfo n = NI { _inCluster :: !(Maybe GraphID) , _attributes :: !Attributes , _predecessors :: !(EdgeMap n) , _successors :: !(EdgeMap n) } deriving (Eq, Ord, Show, Read) data ClusterInfo = CI { parentCluster :: !(Maybe GraphID) , clusterAttrs :: !GlobAttrs } deriving (Eq, Ord, Show, Read) type NodeMap n = Map n (NodeInfo n) type EdgeMap n = Map n [Attributes] -- | The decomposition of a node from a dot graph. Any loops should -- be found in 'successors' rather than 'predecessors'. Note also -- that these are created\/consumed as if for /directed/ graphs. data Context n = Cntxt { node :: !n -- | The cluster this node can be found in; -- @Nothing@ indicates the node can be -- found in the root graph. , inCluster :: !(Maybe GraphID) , attributes :: !Attributes , predecessors :: ![(n, Attributes)] , successors :: ![(n, Attributes)] } deriving (Eq, Ord, Show, Read) adjacent :: Context n -> [DotEdge n] adjacent c = mapU (`DotEdge` n) (predecessors c) ++ mapU (DotEdge n) (successors c) where n = node c mapU = map . uncurry emptyGraph :: DotGraph n emptyGraph = DG { strictGraph = False , directedGraph = True , graphID = Nothing , graphAttrs = emptyGA , clusters = M.empty , values = M.empty } emptyGA :: GlobAttrs emptyGA = GA S.empty S.empty S.empty -- ----------------------------------------------------------------------------- -- Construction -- | Merge the 'Context' into the graph. Assumes that the specified -- node is not in the graph but that all endpoints in the -- 'successors' and 'predecessors' (with the exception of loops) -- are. If the cluster is not present in the graph, then it will be -- added with no attributes with a parent of the root graph. -- -- Note that @&@ and @'decompose'@ are /not/ quite inverses, as this -- function will add in the cluster if it does not yet exist in the -- graph, but 'decompose' will not delete it. (&) :: (Ord n) => Context n -> DotGraph n -> DotGraph n (Cntxt n mc as ps ss) & dg = withValues merge dg' where ps' = toMap ps ps'' = fromMap (M.delete n ps') ss' = toMap ss ss'' = fromMap (M.delete n ss') dg' = addNode n mc as dg merge = addSuccRev n ps'' . addPredRev n ss'' -- Add reverse edges . M.adjust (\ni -> ni { _predecessors = ps', _successors = ss' }) n -- Add actual edges infixr 5 & -- | Recursively merge the list of contexts. -- -- > composeList = foldr (&) emptyGraph composeList :: (Ord n) => [Context n] -> DotGraph n composeList = foldr (&) emptyGraph addSuccRev :: (Ord n) => n -> [(n, Attributes)] -> NodeMap n -> NodeMap n addSuccRev = addEdgeLinks niSkip niSucc addPredRev :: (Ord n) => n -> [(n, Attributes)] -> NodeMap n -> NodeMap n addPredRev = addEdgeLinks niSkip niPred addEdgeLinks :: (Ord n) => UpdateEdgeMap n -> UpdateEdgeMap n -> n -> [(n, Attributes)] -> NodeMap n -> NodeMap n addEdgeLinks fwd rev f tas = updRev . updFwd where updFwd = M.adjust addFwd f addFwd ni = foldl' (\ni' (t,as) -> fwd (M.insertWith (++) t [as]) ni') ni tas updRev nm = foldl' (\nm' (t,as) -> M.adjust (addRev as) t nm') nm tas addRev as = rev (M.insertWith (++) f [as]) -- | Add a node to the current graph. Merges attributes and edges if -- the node already exists in the graph. -- -- If the specified cluster does not yet exist in the graph, then it -- will be added (as a sub-graph of the overall graph and no -- attributes). addNode :: (Ord n) => n -> Maybe GraphID -- ^ The cluster the node can be found in -- (@Nothing@ refers to the root graph). -> Attributes -> DotGraph n -> DotGraph n addNode n mc as dg = addEmptyCluster mc $ dg { values = ns' } where ns = values dg ns' = M.insertWith mergeLogic n (NI mc as M.empty M.empty) ns mergeLogic (NI newClust newAttrs newPreds newSuccs) (NI oldClust oldAttrs oldPreds oldSuccs) = NI resClust resAttrs resPreds resSuccs where resClust = newClust <|> oldClust resAttrs = unSame $ S.union (toSAttr newAttrs) (toSAttr oldAttrs) resPreds = M.unionWith (++) newPreds oldPreds resSuccs = M.unionWith (++) newSuccs oldSuccs -- | A variant of 'addNode' that takes in a DotNode (not in a -- cluster). addDotNode :: (Ord n) => DotNode n -> DotGraph n -> DotGraph n addDotNode (DotNode n as) = addNode n Nothing as -- | Add the specified edge to the graph; assumes both node values are -- already present in the graph. If the graph is undirected then -- the order of nodes doesn't matter. addEdge :: (Ord n) => n -> n -> Attributes -> DotGraph n -> DotGraph n addEdge f t as = withValues merge where merge = addEdgeLinks niSucc niPred f [(t,as)] -- | A variant of 'addEdge' that takes a 'DotEdge' value. addDotEdge :: (Ord n) => DotEdge n -> DotGraph n -> DotGraph n addDotEdge (DotEdge f t as) = addEdge f t as -- | Add a new cluster to the graph; throws an error if the cluster -- already exists. Assumes that it doesn't match the identifier of -- the overall graph. If the parent cluster doesn't already exist -- in the graph then it will be added. addCluster :: GraphID -- ^ The identifier for this cluster. -> Maybe GraphID -- ^ The parent of this cluster -- (@Nothing@ refers to the root -- graph) -> [GlobalAttributes] -> DotGraph n -> DotGraph n addCluster c mp gas dg | c `M.member` cs = error "Cluster already exists in the graph" | otherwise = addEmptyCluster mp $ dg { clusters = M.insert c ci cs } where cs = clusters dg ci = CI mp $ toGlobAttrs gas -- Used to make sure that the parent cluster exists addEmptyCluster :: Maybe GraphID -> DotGraph n -> DotGraph n addEmptyCluster = maybe id (withClusters . (`dontReplace` defCI)) where dontReplace = M.insertWith (const id) defCI = CI Nothing emptyGA -- | Specify the parent of the cluster; adds both in if not already present. setClusterParent :: GraphID -> Maybe GraphID -> DotGraph n -> DotGraph n setClusterParent c p = withClusters (M.adjust setP c) . addCs where addCs = addEmptyCluster p . addEmptyCluster (Just c) setP ci = ci { parentCluster = p } -- | Specify the attributes of the cluster; adds it if not already -- present. setClusterAttributes :: GraphID -> [GlobalAttributes] -> DotGraph n -> DotGraph n setClusterAttributes c gas = withClusters (M.adjust setAs c) . addEmptyCluster (Just c) where setAs ci = ci { clusterAttrs = toGlobAttrs gas } -- | Create a graph with no clusters. mkGraph :: (Ord n) => [DotNode n] -> [DotEdge n] -> DotGraph n mkGraph ns es = flip (foldl' $ flip addDotEdge) es $ foldl' (flip addDotNode) emptyGraph ns -- | Convert this DotGraph into canonical form. All edges are found -- in the outer graph rather than in clusters. toCanonical :: DotGraph n -> C.DotGraph n toCanonical dg = C.DotGraph { C.strictGraph = strictGraph dg , C.directedGraph = directedGraph dg , C.graphID = graphID dg , C.graphStatements = stmts } where stmts = C.DotStmts { C.attrStmts = fromGlobAttrs $ graphAttrs dg , C.subGraphs = cs , C.nodeStmts = ns , C.edgeStmts = getEdgeInfo False dg } cls = clusters dg pM = clusterPath' dg clustAs = maybe [] (fromGlobAttrs . clusterAttrs) . (`M.lookup`cls) lns = map (\ (n,ni) -> (n,(_inCluster ni, _attributes ni))) . M.assocs $ values dg (cs,ns) = clustersToNodes pathOf (const True) id clustAs snd lns pathOf (n,(c,as)) = pathFrom c (n,as) pathFrom c ln = F.foldr C (N ln) . fromMaybe Seq.empty $ (`M.lookup`pM) =<< c -- ----------------------------------------------------------------------------- -- Deconstruction -- | A partial inverse of @'&'@, in that if a node exists in a graph -- then it will be decomposed, but will not remove the cluster that -- it was in even if it was the only node in that cluster. decompose :: (Ord n) => n -> DotGraph n -> Maybe (Context n, DotGraph n) decompose n dg | n `M.notMember` ns = Nothing | otherwise = Just (c, dg') where ns = values dg (Just (NI mc as ps ss), ns') = M.updateLookupWithKey (const . const Nothing) n ns c = Cntxt n mc as (fromMap $ n `M.delete` ps) (fromMap ss) dg' = dg { values = delSucc n ps . delPred n ss $ ns' } -- | As with 'decompose', but do not specify /which/ node to -- decompose. decomposeAny :: (Ord n) => DotGraph n -> Maybe (Context n, DotGraph n) decomposeAny dg | isEmpty dg = Nothing | otherwise = decompose (fst . M.findMin $ values dg) dg -- | Recursively decompose the Dot graph into a list of contexts such -- that if @(c:cs) = decomposeList dg@, then @dg = c & 'composeList' cs@. -- -- Note that all global attributes are lost, so this is /not/ -- suitable for representing a Dot graph on its own. decomposeList :: (Ord n) => DotGraph n -> [Context n] decomposeList = unfoldr decomposeAny delSucc :: (Ord n) => n -> EdgeMap n -> NodeMap n -> NodeMap n delSucc = delPS niSucc delPred :: (Ord n) => n -> EdgeMap n -> NodeMap n -> NodeMap n delPred = delPS niPred -- Only takes in EdgeMap rather than [n] to make it easier to call -- from decompose delPS :: (Ord n) => ((EdgeMap n -> EdgeMap n) -> NodeInfo n -> NodeInfo n) -> n -> EdgeMap n -> NodeMap n -> NodeMap n delPS fni t fm nm = foldl' delE nm $ M.keys fm where delE nm' f = M.adjust (fni $ M.delete t) f nm' -- | Delete the specified node from the graph; returns the original -- graph if that node isn't present. deleteNode :: (Ord n) => n -> DotGraph n -> DotGraph n deleteNode n dg = maybe dg snd $ decompose n dg -- | Delete all edges between the two nodes; returns the original -- graph if there are no edges. deleteAllEdges :: (Ord n) => n -> n -> DotGraph n -> DotGraph n deleteAllEdges n1 n2 = withValues (delAE n1 n2 . delAE n2 n1) where delAE f t = delSucc f t' . delPred f t' where t' = M.singleton t [] -- | Deletes the specified edge from the DotGraph (note: for unordered -- graphs both orientations are considered). deleteEdge :: (Ord n) => n -> n -> Attributes -> DotGraph n -> DotGraph n deleteEdge n1 n2 as dg = withValues delEs dg where delE f t = M.adjust (niSucc $ M.adjust (delete as) t) f . M.adjust (niPred $ M.adjust (delete as) f) t delEs | directedGraph dg = delE n1 n2 | otherwise = delE n1 n2 . delE n2 n1 -- | As with 'deleteEdge' but takes a 'DotEdge' rather than individual -- values. deleteDotEdge :: (Ord n) => DotEdge n -> DotGraph n -> DotGraph n deleteDotEdge (DotEdge n1 n2 as) = deleteEdge n1 n2 as -- | Delete the specified cluster, and makes any clusters or nodes -- within it be in its root cluster (or the overall graph if -- required). deleteCluster :: GraphID -> DotGraph n -> DotGraph n deleteCluster c dg = withValues (M.map adjNode) . withClusters (M.map adjCluster . M.delete c) $ dg where p = parentCluster =<< c `M.lookup` clusters dg adjParent p' | p' == Just c = p | otherwise = p' adjNode ni = ni { _inCluster = adjParent $ _inCluster ni } adjCluster ci = ci { parentCluster = adjParent $ parentCluster ci } -- | Remove clusters with no sub-clusters and no nodes within them. removeEmptyClusters :: DotGraph n -> DotGraph n removeEmptyClusters dg = dg { clusters = cM' } where cM = clusters dg cM' = (cM `M.difference` invCs) `M.difference` invNs invCs = usedClustsIn $ M.map parentCluster cM invNs = usedClustsIn . M.map _inCluster $ values dg usedClustsIn = M.fromAscList . map ((,) <$> fst . head <*> map snd) . groupSortBy fst . mapMaybe (uncurry (fmap . flip (,))) . M.assocs -- ----------------------------------------------------------------------------- -- Information -- | Does this graph have any nodes? isEmpty :: DotGraph n -> Bool isEmpty = M.null . values -- | Does this graph have any clusters? hasClusters :: DotGraph n -> Bool hasClusters = M.null . clusters -- | Determine if this graph has nodes or clusters. isEmptyGraph :: DotGraph n -> Bool isEmptyGraph = liftA2 (&&) isEmpty (not . hasClusters) graphAttributes :: DotGraph n -> [GlobalAttributes] graphAttributes = fromGlobAttrs . graphAttrs -- | Return the ID for the cluster the node is in. foundInCluster :: (Ord n) => DotGraph n -> n -> Maybe GraphID foundInCluster dg n = _inCluster $ values dg M.! n -- | Return the attributes for the node. attributesOf :: (Ord n) => DotGraph n -> n -> Attributes attributesOf dg n = _attributes $ values dg M.! n -- | Predecessor edges for the specified node. For undirected graphs -- equivalent to 'adjacentTo'. predecessorsOf :: (Ord n) => DotGraph n -> n -> [DotEdge n] predecessorsOf dg t | directedGraph dg = emToDE (`DotEdge` t) . _predecessors $ values dg M.! t | otherwise = adjacentTo dg t -- | Successor edges for the specified node. For undirected graphs -- equivalent to 'adjacentTo'. successorsOf :: (Ord n) => DotGraph n -> n -> [DotEdge n] successorsOf dg f | directedGraph dg = emToDE (DotEdge f) . _successors $ values dg M.! f | otherwise = adjacentTo dg f -- | All edges involving this node. adjacentTo :: (Ord n) => DotGraph n -> n -> [DotEdge n] adjacentTo dg n = sucs ++ preds where ni = values dg M.! n sucs = emToDE (DotEdge n) $ _successors ni preds = emToDE (`DotEdge` n) $ n `M.delete` _predecessors ni emToDE :: (n -> Attributes -> DotEdge n) -> EdgeMap n -> [DotEdge n] emToDE f = map (uncurry f) . fromMap -- | Which cluster (or the root graph) is this cluster in? parentOf :: DotGraph n -> GraphID -> Maybe GraphID parentOf dg c = parentCluster $ clusters dg M.! c clusterAttributes :: DotGraph n -> GraphID -> [GlobalAttributes] clusterAttributes dg c = fromGlobAttrs . clusterAttrs $ clusters dg M.! c -- ----------------------------------------------------------------------------- -- For DotRepr instance instance (Ord n) => DotRepr DotGraph n where fromCanonical = fromDotRepr getID = graphID setID i g = g { graphID = Just i } graphIsDirected = directedGraph setIsDirected d g = g { directedGraph = d } graphIsStrict = strictGraph setStrictness s g = g { strictGraph = s } mapDotGraph = mapNs graphStructureInformation = getGraphInfo nodeInformation = getNodeInfo edgeInformation = getEdgeInfo unAnonymise = id -- No anonymous clusters! instance (Ord n) => G.FromGeneralisedDot DotGraph n where fromGeneralised = fromDotRepr instance (Ord n, PrintDot n) => PrintDotRepr DotGraph n instance (Ord n, ParseDot n) => ParseDotRepr DotGraph n instance (Ord n, PrintDot n, ParseDot n) => PPDotRepr DotGraph n -- | Uses the PrintDot instance for canonical 'C.DotGraph's. instance (PrintDot n) => PrintDot (DotGraph n) where unqtDot = unqtDot . toCanonical -- | Uses the ParseDot instance for generalised 'G.DotGraph's. instance (Ord n, ParseDot n) => ParseDot (DotGraph n) where parseUnqt = fromGDot <$> parseUnqt where -- fromGDot :: G.DotGraph n -> DotGraph n fromGDot = fromDotRepr . (`asTypeOf` (undefined :: G.DotGraph n)) parse = parseUnqt -- Don't want the option of quoting cOptions :: CanonicaliseOptions cOptions = COpts { edgesInClusters = False , groupAttributes = True } -- | Convert any existing DotRepr instance to a 'DotGraph'. fromDotRepr :: (DotRepr dg n) => dg n -> DotGraph n fromDotRepr = unsafeFromCanonical . canonicaliseOptions cOptions . unAnonymise -- | Convert a canonical Dot graph to a graph-based one. This assumes -- that the canonical graph is the same format as returned by -- 'toCanonical'. The \"unsafeness\" is that: -- -- * All clusters must have a unique identifier ('unAnonymise' can -- be used to make sure all clusters /have/ an identifier, but it -- doesn't ensure uniqueness). -- -- * All nodes are assumed to be explicitly listed precisely once. -- -- * Only edges found in the root graph are considered. -- -- If this isn't the case, use 'fromCanonical' instead. -- -- The 'graphToDot' function from "Data.GraphViz" produces output -- suitable for this function (assuming all clusters are provided -- with a unique identifier); 'graphElemsToDot' is suitable if all -- nodes are specified in the input list (rather than just the -- edges). unsafeFromCanonical :: (Ord n) => C.DotGraph n -> DotGraph n unsafeFromCanonical dg = DG { strictGraph = C.strictGraph dg , directedGraph = dirGraph , graphAttrs = as , graphID = mgid , clusters = cs , values = ns } where stmts = C.graphStatements dg mgid = C.graphID dg dirGraph = C.directedGraph dg (as, cs, ns) = fCStmt Nothing stmts fCStmt p stmts' = (sgAs, cs', ns') where sgAs = toGlobAttrs $ C.attrStmts stmts' (cs', sgNs) = (M.unions *** M.unions) . unzip . map (fCSG p) $ C.subGraphs stmts' nNs = M.fromList . map (fDN p) $ C.nodeStmts stmts' ns' = sgNs `M.union` nNs fCSG p sg = (M.insert sgid ci cs', ns') where msgid@(Just sgid) = C.subGraphID sg (as', cs', ns') = fCStmt msgid $ C.subGraphStmts sg ci = CI p as' fDN p (DotNode n as') = ( n , NI { _inCluster = p , _attributes = as' , _predecessors = eSel n tEs , _successors = eSel n fEs } ) es = C.edgeStmts stmts fEs = toEdgeMap fromNode toNode es tEs = delLoops $ toEdgeMap toNode fromNode es eSel n es' = fromMaybe M.empty $ n `M.lookup` es' delLoops = M.mapWithKey M.delete toEdgeMap :: (Ord n) => (DotEdge n -> n) -> (DotEdge n -> n) -> [DotEdge n] -> Map n (EdgeMap n) toEdgeMap f t = M.map eM . M.fromList . groupSortCollectBy f t' where t' = liftA2 (,) t edgeAttributes eM = M.fromList . groupSortCollectBy fst snd mapNs :: (Ord n') => (n -> n') -> DotGraph n -> DotGraph n' mapNs f (DG st d as mid cs vs) = DG st d as mid cs $ mapNM vs where mapNM = M.map mapNI . mpM mapNI (NI mc as' ps ss) = NI mc as' (mpM ps) (mpM ss) mpM = M.mapKeys f getGraphInfo :: DotGraph n -> (GlobalAttributes, ClusterLookup) getGraphInfo dg = (gas, cl) where toGA = GraphAttrs . unSame (gas, cgs) = (toGA *** M.map toGA) $ globAttrMap graphAs dg pM = M.map pInit $ clusterPath dg cl = M.mapWithKey addPath $ M.mapKeysMonotonic Just cgs addPath c as = ( maybeToList $ c `M.lookup` pM , as ) pInit p = case Seq.viewr p of (p' Seq.:> _) -> p' _ -> Seq.empty getNodeInfo :: Bool -> DotGraph n -> NodeLookup n getNodeInfo withGlob dg = M.map toLookup ns where (gGlob, aM) = globAttrMap nodeAs dg pM = clusterPath dg ns = values dg toLookup ni = (pth, as') where as = _attributes ni mp = _inCluster ni pth = fromMaybe Seq.empty $ mp `M.lookup` pM pAs = fromMaybe gGlob $ (`M.lookup` aM) =<< mp as' | withGlob = unSame $ toSAttr as `S.union` pAs | otherwise = as getEdgeInfo :: Bool -> DotGraph n -> [DotEdge n] getEdgeInfo withGlob dg = concatMap (uncurry mkDotEdges) es where gGlob = edgeAs $ graphAttrs dg es = concatMap (uncurry (map . (,))) . M.assocs . M.map (M.assocs . _successors) $ values dg addGlob as | withGlob = unSame $ toSAttr as `S.union` gGlob | otherwise = as mkDotEdges f (t, ass) = map (DotEdge f t . addGlob) ass globAttrMap :: (GlobAttrs -> SAttrs) -> DotGraph n -> (SAttrs, Map GraphID SAttrs) globAttrMap af dg = (gGlob, aM) where gGlob = af $ graphAttrs dg cs = clusters dg aM = M.map attrsFor cs attrsFor ci = as `S.union` pAs where as = af $ clusterAttrs ci p = parentCluster ci pAs = fromMaybe gGlob $ (`M.lookup` aM) =<< p clusterPath :: DotGraph n -> Map (Maybe GraphID) St.Path clusterPath = M.mapKeysMonotonic Just . M.map (fmap Just) . clusterPath' clusterPath' :: DotGraph n -> Map GraphID (Seq.Seq GraphID) clusterPath' dg = pM where cs = clusters dg pM = M.mapWithKey pathOf cs pathOf c ci = pPth Seq.|> c where mp = parentCluster ci pPth = fromMaybe Seq.empty $ (`M.lookup` pM) =<< mp -- ----------------------------------------------------------------------------- withValues :: (NodeMap n -> NodeMap n) -> DotGraph n -> DotGraph n withValues f dg = dg { values = f $ values dg } withClusters :: (Map GraphID ClusterInfo -> Map GraphID ClusterInfo) -> DotGraph n -> DotGraph n withClusters f dg = dg { clusters = f $ clusters dg } toGlobAttrs :: [GlobalAttributes] -> GlobAttrs toGlobAttrs = mkGA . partitionGlobal where mkGA (ga,na,ea) = GA (toSAttr ga) (toSAttr na) (toSAttr ea) fromGlobAttrs :: GlobAttrs -> [GlobalAttributes] fromGlobAttrs (GA ga na ea) = filter (not . null . attrs) [ GraphAttrs $ unSame ga , NodeAttrs $ unSame na , EdgeAttrs $ unSame ea ] type UpdateEdgeMap n = (EdgeMap n -> EdgeMap n) -> NodeInfo n -> NodeInfo n niSucc :: UpdateEdgeMap n niSucc f ni = ni { _successors = f $ _successors ni } niPred :: UpdateEdgeMap n niPred f ni = ni { _predecessors = f $ _predecessors ni } niSkip :: UpdateEdgeMap n niSkip _ ni = ni toMap :: (Ord n) => [(n, Attributes)] -> EdgeMap n toMap = M.fromAscList . groupSortCollectBy fst snd fromMap :: EdgeMap n -> [(n, Attributes)] fromMap = concatMap (uncurry (map . (,))) . M.toList graphviz-2999.20.2.0/Data/GraphViz/Types/Monadic.hs0000644000000000000000000002026514535166704017663 0ustar0000000000000000{-# LANGUAGE CPP, FlexibleInstances, MultiParamTypeClasses #-} {- | Module : Data.GraphViz.Types.Monadic Description : A monadic interface for making Dot graphs. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module is based upon the /dotgen/ library by Andy Gill: It provides a monadic interface for constructing generalised Dot graphs. Note that this does /not/ have an instance for @DotRepr@ (e.g. what would be the point of the @fromCanonical@ function, as you can't do anything with the result): it is purely for construction purposes. Use the generalised Dot graph instance for printing, etc. Note that the generalised Dot graph types are /not/ re-exported, in case it causes a clash with other modules you may choose to import. The example graph in "Data.GraphViz.Types" can be written as: > digraph (Str "G") $ do > > cluster (Int 0) $ do > graphAttrs [style filled, color LightGray] > nodeAttrs [style filled, color White] > "a0" --> "a1" > "a1" --> "a2" > "a2" --> "a3" > graphAttrs [textLabel "process #1"] > > cluster (Int 1) $ do > nodeAttrs [style filled] > "b0" --> "b1" > "b1" --> "b2" > "b2" --> "b3" > graphAttrs [textLabel "process #2", color Blue] > > "start" --> "a0" > "start" --> "b0" > "a1" --> "b3" > "b2" --> "a3" > "a3" --> "end" > "b3" --> "end" > > node "start" [shape MDiamond] > node "end" [shape MSquare] -} module Data.GraphViz.Types.Monadic ( Dot , DotM , GraphID(..) -- * Creating a generalised DotGraph. , digraph , digraph' , graph , graph' -- * Adding global attributes. , graphAttrs , nodeAttrs , edgeAttrs -- * Adding items to the graph. -- ** Subgraphs and clusters , subgraph , anonSubgraph , cluster -- ** Nodes , node , node' -- ** Edges -- $edges , edge , (-->) , (<->) ) where import Data.GraphViz.Attributes (Attributes) import Data.GraphViz.Types.Generalised import Data.DList (DList) import qualified Data.DList as DL import qualified Data.Sequence as Seq #if !(MIN_VERSION_base (4,8,0)) import Control.Applicative (Applicative(..)) import Data.Monoid (Monoid(..)) #endif #if MIN_VERSION_base (4,9,0) && !MIN_VERSION_base (4,13,0) import Data.Semigroup (Semigroup(..)) #endif import Control.Monad.Fix (MonadFix (mfix)) -- ----------------------------------------------------------------------------- -- The Dot monad. -- | The monadic representation of a Dot graph. type Dot n = DotM n () -- | The actual monad; as with 'Dot' but allows you to return a value -- within the do-block. The actual implementation is based upon the -- Writer monad. newtype DotM n a = DotM { runDot :: (a, DotStmts n) } execDot :: DotM n a -> DotStmts n execDot = snd . runDot instance Functor (DotM n) where fmap f (DotM (a,stmts)) = DotM (f a, stmts) instance Applicative (DotM n) where pure = DotM . flip (,) DL.empty (DotM (f,stmts1)) <*> (DotM (a,stmts2)) = DotM (f a, stmts1 `DL.append` stmts2) instance Monad (DotM n) where return = pure dt >>= f = DotM $ let ~(a,stmts) = runDot dt ~(b,stmts') = runDot $ f a in (b, stmts `DL.append` stmts') instance MonadFix (DotM n) where mfix m = let (a,n) = runDot $ m a in DotM (a,n) #if MIN_VERSION_base (4,9,0) instance Semigroup a => Semigroup (DotM n a) where DotM x1 <> DotM x2 = DotM (x1 <> x2) #endif instance Monoid a => Monoid (DotM n a) where mappend (DotM x1) (DotM x2) = DotM (mappend x1 x2) mempty = DotM mempty tell :: DotStmts n -> Dot n tell = DotM . (,) () tellStmt :: DotStmt n -> Dot n tellStmt = tell . DL.singleton -- ----------------------------------------------------------------------------- -- Creating the DotGraph -- | Create a directed dot graph with the specified graph ID. digraph :: GraphID -> DotM n a -> DotGraph n digraph = mkGraph True . Just -- | Create a directed dot graph with no graph ID. digraph' :: DotM n a -> DotGraph n digraph' = mkGraph True Nothing -- | Create a undirected dot graph with the specified graph ID. graph :: GraphID -> DotM n a -> DotGraph n graph = mkGraph False . Just -- | Create a undirected dot graph with no graph ID. graph' :: DotM n a -> DotGraph n graph' = mkGraph False Nothing mkGraph :: Bool -> Maybe GraphID -> DotM n a -> DotGraph n mkGraph isDir mid dot = DotGraph { strictGraph = False , directedGraph = isDir , graphID = mid , graphStatements = execStmts dot } -- ----------------------------------------------------------------------------- -- Statements type DotStmts n = DList (DotStmt n) execStmts :: DotM n a -> DotStatements n execStmts = convertStatements . execDot convertStatements :: DotStmts n -> DotStatements n convertStatements = Seq.fromList . map convertStatement . DL.toList data DotStmt n = MA GlobalAttributes | MS (Subgraph n) | MN (DotNode n) | ME (DotEdge n) convertStatement :: DotStmt n -> DotStatement n convertStatement (MA gas) = GA gas convertStatement (MS sg) = SG . DotSG (sgIsClust sg) (sgID sg) . execStmts $ sgStmts sg convertStatement (MN dn) = DN dn convertStatement (ME de) = DE de -- ----------------------------------------------------------------------------- -- Global Attributes -- | Add graph\/sub-graph\/cluster attributes. graphAttrs :: Attributes -> Dot n graphAttrs = tellStmt . MA . GraphAttrs -- | Add global node attributes. nodeAttrs :: Attributes -> Dot n nodeAttrs = tellStmt . MA . NodeAttrs -- | Add global edge attributes edgeAttrs :: Attributes -> Dot n edgeAttrs = tellStmt . MA . EdgeAttrs -- ----------------------------------------------------------------------------- -- Subgraphs (including Clusters) data Subgraph n = Sg { sgIsClust :: Bool , sgID :: Maybe GraphID , sgStmts :: Dot n } -- | Add a named subgraph to the graph. subgraph :: GraphID -> DotM n a -> Dot n subgraph = nonClust . Just -- | Add an anonymous subgraph to the graph. -- -- It is highly recommended you use 'subgraph' instead. anonSubgraph :: DotM n a -> Dot n anonSubgraph = nonClust Nothing nonClust :: Maybe GraphID -> DotM n a -> Dot n nonClust = createSubGraph False createSubGraph :: Bool -> Maybe GraphID -> DotM n a -> Dot n createSubGraph isCl mid = tellStmt . MS . Sg isCl mid . (>> return ()) -- | Add a named cluster to the graph. cluster :: GraphID -> DotM n a -> Dot n cluster = createSubGraph True . Just -- ----------------------------------------------------------------------------- -- Nodes -- | Add a node to the graph. node :: n -> Attributes -> Dot n node n = tellStmt . MN . DotNode n -- | Add a node with no attributes to the graph. node' :: n -> Dot n node' = (`node` []) -- ----------------------------------------------------------------------------- -- Edges {- $edges If you wish to use something analogous to Dot's ability to write multiple edges with in-line subgraphs such as: > {a b c} -> {d e f} Then you can use '-->' and '<->' in combination with monadic traversal functions such as @traverse_@, @for_@, @mapM_@, @forM_@ and @zipWithM_@; for example: > ("a" -->) `traverse_` ["d", "e", "f"] > ["a", "b", "c"] `for_` (--> "d") > zipWithM_ (-->) ["a", "b", "c"] ["d", "e", "f"] -} -- | Add an edge to the graph. edge :: n -> n -> Attributes -> Dot n edge f t = tellStmt . ME . DotEdge f t -- | Add an edge with no attributes. (-->) :: n -> n -> Dot n f --> t = edge f t [] infixr 9 --> -- | An alias for '-->' to make edges look more undirected. (<->) :: n -> n -> Dot n (<->) = (-->) infixr 9 <-> -- ----------------------------------------------------------------------------- graphviz-2999.20.2.0/Data/GraphViz/Parsing.hs0000644000000000000000000004361514535166704016614 0ustar0000000000000000{-# LANGUAGE FlexibleInstances, OverloadedStrings #-} {- | Module : Data.GraphViz.Parsing Description : Helper functions for Parsing. Copyright : (c) Matthew Sackman, Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module defines simple helper functions for use with "Text.ParserCombinators.Poly.Lazy". Note that the 'ParseDot' instances for 'Bool', etc. match those specified for use with Graphviz (e.g. non-zero integers are equivalent to 'True'). You should not be using this module; rather, it is here for informative/documentative reasons. If you want to parse a @'Data.GraphViz.Types.DotRepr'@, you should use @'Data.GraphViz.Types.parseDotGraph'@ rather than its 'ParseDot' instance. -} module Data.GraphViz.Parsing ( -- * Re-exporting pertinent parts of Polyparse. module Text.ParserCombinators.Poly.StateText -- * The ParseDot class. , Parse , ParseDot(..) , parseIt , parseIt' , runParser , runParser' , runParserWith , parseLiberally , checkValidParse , checkValidParseWithRest -- * Convenience parsing combinators. , ignoreSep , onlyBool , quotelessString , stringBlock , numString , isNumString , isIntString , quotedString , parseEscaped , parseAndSpace , string , strings , character , parseStrictFloat , parseSignedFloat , noneOf , whitespace1 , whitespace , wrapWhitespace , optionalQuotedString , optionalQuoted , quotedParse , orQuote , quoteChar , newline , newline' , parseComma , parseEq , tryParseList , tryParseList' , consumeLine , commaSep , commaSepUnqt , commaSep' , stringRep , stringReps , stringParse , stringValue , parseAngled , parseBraced , parseColorScheme ) where import Data.GraphViz.Exception (GraphvizException(NotDotCode), throw) import Data.GraphViz.Internal.State import Data.GraphViz.Internal.Util -- To avoid orphan instances and cyclic imports import Data.GraphViz.Attributes.ColorScheme import Text.ParserCombinators.Poly.StateText hiding (empty, indent, runParser) import qualified Text.ParserCombinators.Poly.StateText as P import Control.Arrow (first, second) import Control.Monad (when) import Data.Char (isDigit, isLower, isSpace, toLower, toUpper) import Data.Function (on) import Data.List (groupBy, sortBy) import Data.Maybe (fromMaybe, isJust, isNothing, listToMaybe, maybeToList) import Data.Ratio ((%)) import qualified Data.Set as Set import qualified Data.Text as ST import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T import qualified Data.Text.Lazy.Read as T import Data.Version (Version(..)) import Data.Word (Word16, Word8) -- ----------------------------------------------------------------------------- -- Based off code from Text.Parse in the polyparse library -- | A @ReadS@-like type alias. type Parse a = Parser GraphvizState a runParser :: Parse a -> Text -> (Either String a, Text) runParser = runParserWith id parseLiberally :: GraphvizState -> GraphvizState parseLiberally gs = gs { parseStrictly = False } runParserWith :: (GraphvizState -> GraphvizState) -> Parse a -> Text -> (Either String a, Text) runParserWith f p t = let (r,_,t') = P.runParser p (f initialState) t in (r,t') -- | A variant of 'runParser' where it is assumed that the provided -- parsing function consumes all of the 'Text' input (with the -- exception of whitespace at the end). runParser' :: Parse a -> Text -> a runParser' p = checkValidParseWithRest . runParser p' where p' = p `discard` (whitespace *> eof) class ParseDot a where parseUnqt :: Parse a parse :: Parse a parse = optionalQuoted parseUnqt parseUnqtList :: Parse [a] parseUnqtList = bracketSep (parseAndSpace $ character '[') ( wrapWhitespace parseComma `onFail` whitespace1 ) (whitespace *> character ']') parseUnqt parseList :: Parse [a] parseList = quotedParse parseUnqtList -- | Parse the required value, returning also the rest of the input -- 'Text' that hasn't been parsed (for debugging purposes). parseIt :: (ParseDot a) => Text -> (a, Text) parseIt = first checkValidParse . runParser parse -- | If unable to parse /Dot/ code properly, 'throw' a -- 'GraphvizException'. checkValidParse :: Either String a -> a checkValidParse (Left err) = throw (NotDotCode err) checkValidParse (Right a) = a -- | If unable to parse /Dot/ code properly, 'throw' a -- 'GraphvizException', with the error containing the remaining -- unparsed code.. checkValidParseWithRest :: (Either String a, Text) -> a checkValidParseWithRest (Left err, rst) = throw (NotDotCode err') where err' = err ++ "\n\nRemaining input:\n\t" ++ show rst checkValidParseWithRest (Right a,_) = a -- | Parse the required value with the assumption that it will parse -- all of the input 'Text'. parseIt' :: (ParseDot a) => Text -> a parseIt' = runParser' parse instance ParseDot Int where parseUnqt = parseSignedInt instance ParseDot Integer where parseUnqt = parseSigned parseInt instance ParseDot Word8 where parseUnqt = parseInt instance ParseDot Word16 where parseUnqt = parseInt instance ParseDot Double where parseUnqt = parseSignedFloat True parse = quotedParse parseUnqt <|> parseSignedFloat False parseUnqtList = sepBy1 parseUnqt (character ':') parseList = quotedParse parseUnqtList `onFail` fmap (:[]) parse instance ParseDot Bool where parseUnqt = onlyBool `onFail` fmap (zero /=) parseSignedInt where zero :: Int zero = 0 -- | Use this when you do not want numbers to be treated as 'Bool' values. onlyBool :: Parse Bool onlyBool = oneOf [ stringRep True "true" , stringRep False "false" ] instance ParseDot Char where -- Can't be a quote character. parseUnqt = satisfy (quoteChar /=) parse = satisfy restIDString `onFail` quotedParse parseUnqt parseUnqtList = T.unpack <$> parseUnqt parseList = T.unpack <$> parse -- | Ignores 'versionTags' and assumes 'not . null . versionBranch' -- (usually you want 'length . versionBranch == 2') and that all -- such values are non-negative. instance ParseDot Version where parseUnqt = createVersion <$> sepBy1 (parseIntCheck False) (character '.') parse = quotedParse parseUnqt <|> (createVersion .) . (. maybeToList) . (:) <$> (parseIntCheck False) <*> optional (character '.' *> parseInt) -- Leave the last one to check for possible decimals -- afterwards as there should be at most two version -- numbers here. instance ParseDot Text where -- Too many problems with using this within other parsers where -- using numString or stringBlock will cause a parse failure. As -- such, this will successfully parse all un-quoted Texts. parseUnqt = quotedString parse = quotelessString `onFail` -- This will also take care of quoted versions of -- above. quotedParse quotedString instance ParseDot ST.Text where parseUnqt = T.toStrict <$> parseUnqt parse = T.toStrict <$> parse instance (ParseDot a) => ParseDot [a] where parseUnqt = parseUnqtList parse = parseList -- | Parse a 'Text' that doesn't need to be quoted. quotelessString :: Parse Text quotelessString = numString False `onFail` stringBlock numString :: Bool -> Parse Text numString q = fmap tShow (parseStrictFloat q) `onFail` fmap tShow parseSignedInt where tShow :: (Show a) => a -> Text tShow = T.pack . show stringBlock :: Parse Text stringBlock = liftA2 T.cons (satisfy frstIDString) (manySatisfy restIDString) -- | Used when quotes are explicitly required; quotedString :: Parse Text quotedString = parseEscaped True [] [] parseSigned :: (Num a) => Parse a -> Parse a parseSigned p = (character '-' *> fmap negate p) `onFail` p parseInt :: (Integral a) => Parse a parseInt = parseIntCheck True -- | Flag indicates whether to check whether the number is actually a -- floating-point value. parseIntCheck :: (Integral a) => Bool -> Parse a parseIntCheck ch = do cs <- many1Satisfy isDigit `adjustErr` ("Expected one or more digits\n\t"++) case T.decimal cs of Right (n,"") -> bool return checkInt ch n -- This case should never actually happen... Right (_,txt) -> fail $ "Trailing digits not parsed as Integral: " ++ T.unpack txt Left err -> fail $ "Could not read Integral: " ++ err where checkInt n = do c <- optional $ oneOf [ character '.', character 'e' ] if isJust c then fail "This number is actually Floating, not Integral!" else return n parseSignedInt :: Parse Int parseSignedInt = parseSigned parseInt -- | Parse a floating point number that actually contains decimals. -- Bool flag indicates whether values that need to be quoted are -- parsed. parseStrictFloat :: Bool -> Parse Double parseStrictFloat = parseSigned . parseFloat -- | Bool flag indicates whether to allow parsing exponentiated term, -- as this is only allowed when quoted. parseFloat :: (RealFrac a) => Bool -> Parse a parseFloat q = do ds <- manySatisfy isDigit frac <- optional $ character '.' *> manySatisfy isDigit when (T.null ds && noDec frac) (fail "No actual digits in floating point number!") expn <- bool (pure Nothing) (optional parseExp) q when (isNothing frac && isNothing expn) (fail "This is an integer, not a floating point number!") let frac' = fromMaybe "" frac expn' = fromMaybe 0 expn ( return . fromRational . (* (10^^(expn' - fromIntegral (T.length frac')))) . (%1) . runParser' parseInt) (ds `T.append` frac') `onFail` fail "Expected a floating point number" where parseExp = character 'e' *> ((character '+' *> parseInt) `onFail` parseSignedInt) noDec = maybe True T.null -- Bool indicates whether we can parse values that need quotes. parseSignedFloat :: Bool -> Parse Double parseSignedFloat q = parseSigned ( parseFloat q <|> fmap fI parseInt ) where fI :: Integer -> Double fI = fromIntegral -- ----------------------------------------------------------------------------- parseAndSpace :: Parse a -> Parse a parseAndSpace p = p `discard` whitespace string :: String -> Parse () string = mapM_ character stringRep :: a -> String -> Parse a stringRep v = stringReps v . return stringReps :: a -> [String] -> Parse a stringReps v ss = oneOf (map string ss) *> return v stringParse :: [(String, Parse a)] -> Parse a stringParse = toPM . sortBy (flip compare `on` fst) where toPM = oneOf . map mkPM . groupBy ((==) `on` (listToMaybe . fst)) mkPM [("",p)] = p mkPM [(str,p)] = string str *> p mkPM kv = character (head . fst $ head kv) *> toPM (map (first tail) kv) stringValue :: [(String, a)] -> Parse a stringValue = stringParse . map (second return) strings :: [String] -> Parse () strings = oneOf . map string -- | Assumes that any letter is ASCII for case-insensitive -- comparisons. character :: Char -> Parse Char character c = satisfy parseC `adjustErr` (const $ "Not the expected character: " ++ [c]) where parseC c' = c' == c || c == flipCase c' flipCase c' = if isLower c' then toUpper c' else toLower c' noneOf :: [Char] -> Parse Char noneOf t = satisfy (\x -> all (/= x) t) -- | Parses at least one whitespace character. whitespace1 :: Parse () whitespace1 = many1Satisfy isSpace *> return () -- | Parses zero or more whitespace characters. whitespace :: Parse () whitespace = manySatisfy isSpace *> return () -- | Parse and discard optional surrounding whitespace. wrapWhitespace :: Parse a -> Parse a wrapWhitespace = bracket whitespace whitespace optionalQuotedString :: String -> Parse () optionalQuotedString = optionalQuoted . string optionalQuoted :: Parse a -> Parse a optionalQuoted p = quotedParse p `onFail` p quotedParse :: Parse a -> Parse a quotedParse = bracket parseQuote parseQuote parseQuote :: Parse () parseQuote = character quoteChar *> return () orQuote :: Parse Char -> Parse Char orQuote p = stringRep quoteChar "\\\"" `onFail` p quoteChar :: Char quoteChar = '"' -- | Parse a 'Text' where the provided 'Char's (as well as @\"@ and -- @\\@) are escaped and the second list of 'Char's are those that -- are not permitted. Note: does not parse surrounding quotes. The -- 'Bool' value indicates whether empty 'Text's are allowed or not. parseEscaped :: Bool -> [Char] -> [Char] -> Parse Text parseEscaped empt cs bnd = fmap T.pack . lots $ qPrs `onFail` oth where lots = if empt then many else many1 cs' = quoteChar : slash : cs csSet = Set.fromList cs' bndSet = Set.fromList bnd `Set.union` csSet slash = '\\' -- Have to allow standard slashes qPrs = fromMaybe slash <$> (character slash *> optional (oneOf $ map character cs') ) oth = satisfy (`Set.notMember` bndSet) -- | Parses a newline. newline :: Parse () newline = strings ["\r\n", "\n", "\r"] -- | Consume all whitespace and newlines until a line with -- non-whitespace is reached. The whitespace on that line is -- not consumed. newline' :: Parse () newline' = many (whitespace *> newline) *> return () -- | Parses and returns all characters up till the end of the line, -- but does not touch the newline characters. consumeLine :: Parse Text consumeLine = manySatisfy (`notElem` ['\n','\r']) parseEq :: Parse () parseEq = wrapWhitespace (character '=') *> return () -- | The opposite of 'bracket'. ignoreSep :: (a -> b -> c) -> Parse a -> Parse sep -> Parse b -> Parse c ignoreSep f pa sep pb = f <$> pa <* sep <*> pb commaSep :: (ParseDot a, ParseDot b) => Parse (a, b) commaSep = commaSep' parse parse commaSepUnqt :: (ParseDot a, ParseDot b) => Parse (a, b) commaSepUnqt = commaSep' parseUnqt parseUnqt commaSep' :: Parse a -> Parse b -> Parse (a,b) commaSep' pa pb = ignoreSep (,) pa (wrapWhitespace parseComma) pb parseComma :: Parse () parseComma = character ',' *> return () -- | Try to parse a list of the specified type; returns an empty list -- if parsing fails. tryParseList :: (ParseDot a) => Parse [a] tryParseList = tryParseList' parse -- | Return an empty list if parsing a list fails. tryParseList' :: Parse [a] -> Parse [a] tryParseList' = fmap (fromMaybe []) . optional parseAngled :: Parse a -> Parse a parseAngled = bracket (character '<') (character '>') parseBraced :: Parse a -> Parse a parseBraced = bracket (character '{') (character '}') -- ----------------------------------------------------------------------------- -- These instances are defined here to avoid cyclic imports and orphan instances instance ParseDot ColorScheme where parseUnqt = parseColorScheme True parseColorScheme :: Bool -> Parse ColorScheme parseColorScheme scs = do cs <- oneOf [ stringRep X11 "X11" , stringRep SVG "svg" , Brewer <$> parseUnqt ] when scs $ setColorScheme cs return cs instance ParseDot BrewerScheme where parseUnqt = liftA2 BScheme parseUnqt parseUnqt instance ParseDot BrewerName where -- The order is different from above to make sure longer names are -- parsed first. parseUnqt = stringValue [ ("accent", Accent) , ("blues", Blues) , ("brbg", Brbg) , ("bugn", Bugn) , ("bupu", Bupu) , ("dark2", Dark2) , ("gnbu", Gnbu) , ("greens", Greens) , ("greys", Greys) , ("oranges", Oranges) , ("orrd", Orrd) , ("paired", Paired) , ("pastel1", Pastel1) , ("pastel2", Pastel2) , ("piyg", Piyg) , ("prgn", Prgn) , ("pubugn", Pubugn) , ("pubu", Pubu) , ("puor", Puor) , ("purd", Purd) , ("purples", Purples) , ("rdbu", Rdbu) , ("rdgy", Rdgy) , ("rdpu", Rdpu) , ("rdylbu", Rdylbu) , ("rdylgn", Rdylgn) , ("reds", Reds) , ("set1", Set1) , ("set2", Set2) , ("set3", Set3) , ("spectral", Spectral) , ("ylgnbu", Ylgnbu) , ("ylgn", Ylgn) , ("ylorbr", Ylorbr) , ("ylorrd", Ylorrd) ] graphviz-2999.20.2.0/Data/GraphViz/Printing.hs0000644000000000000000000003073614535166704017003 0ustar0000000000000000{-# LANGUAGE CPP, FlexibleInstances, GeneralizedNewtypeDeriving, OverloadedStrings #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {- | Module : Data.GraphViz.Printing Description : Helper functions for converting to Dot format. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module defines simple helper functions for use with "Text.PrettyPrint". It also re-exports all the pretty-printing combinators from that module. Note that the 'PrintDot' instances for 'Bool', etc. match those specified for use with Graphviz. You should only be using this module if you are writing custom node types for use with "Data.GraphViz.Types". For actual printing of code, use @'Data.GraphViz.Types.printDotGraph'@ (which produces a 'Text' value). The Dot language specification specifies that any identifier is in one of four forms: * Any string of alphabetic ([a-zA-Z\\200-\\377]) characters, underscores ('_') or digits ([0-9]), not beginning with a digit; * a number [-]?(.[0-9]+ | [0-9]+(.[0-9]*)? ); * any double-quoted string (\"...\") possibly containing escaped quotes (\\\"); * an HTML string (\<...\>). (Note that the first restriction is referring to a byte-by-byte comparison using octal values; when using UTF-8 this corresponds to all characters @c@ where @ord c >= 128@.) Due to these restrictions, you should only use 'text' when you are sure that the 'Text' in question is static and quotes are definitely needed/unneeded; it is better to use the 'Text' instance for 'PrintDot'. For more information, see the specification page: -} module Data.GraphViz.Printing ( module Text.PrettyPrint.Leijen.Text.Monadic , DotCode , DotCodeM , runDotCode , renderDot -- Exported for Data.GraphViz.Types.Internal.Common.printSGID , PrintDot(..) , unqtText , dotText , printIt , addQuotes , unqtEscaped , printEscaped , wrap , commaDel , printField , angled , fslash , printColorScheme ) where import Data.GraphViz.Internal.State import Data.GraphViz.Internal.Util -- To avoid orphan instances and cyclic imports import Data.GraphViz.Attributes.ColorScheme -- Only implicitly import and re-export combinators. import qualified Data.Text as ST import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T import Text.PrettyPrint.Leijen.Text.Monadic hiding (Pretty(..), SimpleDoc(..), bool, displayIO, displayT, hPutDoc, putDoc, renderCompact, renderPretty, string, width, (<$>)) import qualified Text.PrettyPrint.Leijen.Text.Monadic as PP import Control.Monad (ap, when) import Control.Monad.State (MonadState, State, evalState, gets, modify) import Data.Char (toLower) import qualified Data.Set as Set import Data.String (IsString(..)) import Data.Version (Version(..)) import Data.Word (Word64, Word32, Word16, Word8) #if !(MIN_VERSION_base (4,11,0)) #if !(MIN_VERSION_base (4,8,0)) import Control.Applicative (Applicative) import Data.Monoid (Monoid(..)) #endif #if MIN_VERSION_base (4,9,0) && !MIN_VERSION_base (4,13,0) import Data.Semigroup (Semigroup(..)) #else import Data.Monoid ((<>)) #endif #endif -- ----------------------------------------------------------------------------- -- | A type alias to indicate what is being produced. newtype DotCodeM a = DotCodeM { getDotCode :: State GraphvizState a } deriving (Functor, Applicative, Monad, MonadState GraphvizState) type DotCode = DotCodeM Doc runDotCode :: DotCode -> Doc runDotCode = (`evalState` initialState) . getDotCode instance Show DotCode where showsPrec d = showsPrec d . renderDot instance IsString DotCode where fromString = PP.string . fromString #if MIN_VERSION_base (4,9,0) instance Semigroup DotCode where (<>) = beside instance Monoid DotCode where mempty = empty mappend = (<>) #else instance Monoid DotCode where mempty = empty mappend = beside #endif instance GraphvizStateM DotCodeM where modifyGS = modify getsGS = gets -- | Correctly render Graphviz output. renderDot :: DotCode -> Text renderDot = PP.displayT . PP.renderPretty 0.4 80 . runDotCode -- | A class used to correctly print parts of the Graphviz Dot language. -- Minimal implementation is 'unqtDot'. class PrintDot a where -- | The unquoted representation, for use when composing values to -- produce a larger printing value. unqtDot :: a -> DotCode -- | The actual quoted representation; this should be quoted if it -- contains characters not permitted a plain ID String, a number -- or it is not an HTML string. Defaults to 'unqtDot'. toDot :: a -> DotCode toDot = unqtDot -- | The correct way of representing a list of this value when -- printed; not all Dot values require this to be implemented. -- Defaults to Haskell-like list representation. unqtListToDot :: [a] -> DotCode unqtListToDot = list . mapM unqtDot -- | The quoted form of 'unqtListToDot'; defaults to wrapping double -- quotes around the result of 'unqtListToDot' (since the default -- implementation has characters that must be quoted). listToDot :: [a] -> DotCode listToDot = dquotes . unqtListToDot -- | Convert to DotCode; note that this has no indentation, as we can -- only have one of indentation and (possibly) infinite line lengths. printIt :: (PrintDot a) => a -> Text printIt = renderDot . toDot instance PrintDot Int where unqtDot = int instance PrintDot Integer where unqtDot = text . T.pack . show instance PrintDot Word8 where unqtDot = int . fromIntegral instance PrintDot Word16 where unqtDot = int . fromIntegral instance PrintDot Word32 where unqtDot = unqtDot . toInteger instance PrintDot Word64 where unqtDot = unqtDot . toInteger instance PrintDot Double where -- If it's an "integral" double, then print as an integer. This -- seems to match how Graphviz apps use Dot. unqtDot d = if d == fromIntegral di then int di else double d where di = round d toDot d = if any ((==) 'e' . toLower) $ show d then dquotes ud else ud where ud = unqtDot d unqtListToDot = hcat . punctuate colon . mapM unqtDot listToDot [d] = toDot d listToDot ds = dquotes $ unqtListToDot ds instance PrintDot Bool where unqtDot True = text "true" unqtDot False = text "false" instance PrintDot Char where unqtDot = char toDot = qtChar unqtListToDot = unqtDot . T.pack listToDot = toDot . T.pack -- | Ignores 'versionTags' and assumes 'not . null . versionBranch' -- (usually you want 'length . versionBranch == 2'). instance PrintDot Version where unqtDot = hcat . punctuate dot . mapM int . versionBranch toDot v = bool id dquotes (not . null . drop 2 . versionBranch $ v) $ unqtDot v instance PrintDot Text where unqtDot = unqtString toDot = qtString instance PrintDot ST.Text where unqtDot = unqtDot . T.fromStrict toDot = qtString . T.fromStrict -- | For use with @OverloadedStrings@ to avoid ambiguous type variable errors. unqtText :: Text -> DotCode unqtText = unqtDot -- | For use with @OverloadedStrings@ to avoid ambiguous type variable errors. dotText :: Text -> DotCode dotText = toDot -- | Check to see if this 'Char' needs to be quoted or not. qtChar :: Char -> DotCode qtChar c | restIDString c = char c -- Could be a number as well. | otherwise = dquotes $ char c needsQuotes :: Text -> Bool needsQuotes str | T.null str = True | isKeyword str = True | isIDString str = False | isNumString False str = False | otherwise = True addQuotes :: Text -> DotCode -> DotCode addQuotes = bool id dquotes . needsQuotes -- | Escape quotes in Strings that need them. unqtString :: Text -> DotCode unqtString "" = empty unqtString str = unqtEscaped [] str -- no quotes? no worries! -- | Escape quotes and quote Texts that need them (including keywords). qtString :: Text -> DotCode qtString = printEscaped [] instance (PrintDot a) => PrintDot [a] where unqtDot = unqtListToDot toDot = listToDot wrap :: DotCode -> DotCode -> DotCode -> DotCode wrap b a d = b <> d <> a commaDel :: (PrintDot a, PrintDot b) => a -> b -> DotCode commaDel a b = unqtDot a <> comma <> unqtDot b printField :: (PrintDot a) => Text -> a -> DotCode printField f v = text f <> equals <> toDot v -- | Escape the specified chars as well as @\"@. unqtEscaped :: [Char] -> Text -> DotCode unqtEscaped cs = text . addEscapes cs -- | Escape the specified chars as well as @\"@ and then wrap the -- result in quotes. printEscaped :: [Char] -> Text -> DotCode printEscaped cs str = addQuotes str' $ text str' where str' = addEscapes cs str -- | Ensure the provided characters are all escaped. Note that we -- cannot convert to 'DotCode' immediately because 'printEscaped' -- needs to pass the result from this to 'addQuotes' to determine if -- it needs to be quoted or not. addEscapes :: [Char] -> Text -> Text addEscapes cs = foldr escape T.empty . withNext where cs' = Set.fromList $ quote : slash : cs slash = '\\' quote = '"' escape (c,c') str | c == slash && c' `Set.member` escLetters = c `T.cons` str | c `Set.member` cs' = slash `T.cons` (c `T.cons` str) | c == '\n' = slash `T.cons` ('n' `T.cons` str) | otherwise = c `T.cons` str -- When a slash precedes one of these characters, don't escape the slash. escLetters = Set.fromList ['N', 'G', 'E', 'T', 'H', 'L', 'n', 'l', 'r'] -- Need to check subsequent characters when escaping slashes, but -- don't want to lose the last character when zipping, so append a space. withNext "" = [] withNext str = T.zip `ap` ((`T.snoc` ' ') . T.tail) $ str angled :: DotCode -> DotCode angled = wrap langle rangle fslash :: DotCode fslash = char '/' -- ----------------------------------------------------------------------------- -- These instances are defined here to avoid cyclic imports and orphan instances instance PrintDot ColorScheme where unqtDot = printColorScheme True printColorScheme :: Bool -> ColorScheme -> DotCode printColorScheme scs cs = do when scs $ setColorScheme cs case cs of X11 -> unqtText "X11" SVG -> unqtText "svg" Brewer bs -> unqtDot bs instance PrintDot BrewerScheme where unqtDot (BScheme n l) = unqtDot n <> unqtDot l instance PrintDot BrewerName where unqtDot Accent = unqtText "accent" unqtDot Blues = unqtText "blues" unqtDot Brbg = unqtText "brbg" unqtDot Bugn = unqtText "bugn" unqtDot Bupu = unqtText "bupu" unqtDot Dark2 = unqtText "dark2" unqtDot Gnbu = unqtText "gnbu" unqtDot Greens = unqtText "greens" unqtDot Greys = unqtText "greys" unqtDot Oranges = unqtText "oranges" unqtDot Orrd = unqtText "orrd" unqtDot Paired = unqtText "paired" unqtDot Pastel1 = unqtText "pastel1" unqtDot Pastel2 = unqtText "pastel2" unqtDot Piyg = unqtText "piyg" unqtDot Prgn = unqtText "prgn" unqtDot Pubu = unqtText "pubu" unqtDot Pubugn = unqtText "pubugn" unqtDot Puor = unqtText "puor" unqtDot Purd = unqtText "purd" unqtDot Purples = unqtText "purples" unqtDot Rdbu = unqtText "rdbu" unqtDot Rdgy = unqtText "rdgy" unqtDot Rdpu = unqtText "rdpu" unqtDot Rdylbu = unqtText "rdylbu" unqtDot Rdylgn = unqtText "rdylgn" unqtDot Reds = unqtText "reds" unqtDot Set1 = unqtText "set1" unqtDot Set2 = unqtText "set2" unqtDot Set3 = unqtText "set3" unqtDot Spectral = unqtText "spectral" unqtDot Ylgn = unqtText "ylgn" unqtDot Ylgnbu = unqtText "ylgnbu" unqtDot Ylorbr = unqtText "ylorbr" unqtDot Ylorrd = unqtText "ylorrd" graphviz-2999.20.2.0/Data/GraphViz/Commands.hs0000644000000000000000000003240114535166704016741 0ustar0000000000000000{-# LANGUAGE MultiParamTypeClasses, OverloadedStrings #-} {- | Module : Data.GraphViz.Commands Description : Functions to run Graphviz commands. Copyright : (c) Matthew Sackman, Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module defines functions to call the various Graphviz commands. Whilst various output formats are supported (see 'GraphvizOutput' for a complete list), it is not yet possible to choose a desired renderer and formatter. Being able to determine which renderers and formatters are applicable for a specific 'GraphvizOutput' is not easy (there is no listing of available renderers or formatters on the Graphviz website), and for the most part the default ones do the job well. Please note that for 'GraphvizOutput' and 'GraphvizCanvas', you will see that they are instances of a @GraphvizResult@ class; this is an internal class that should not be visible outside this module, but Haddock is being too helpful for its own good. -} module Data.GraphViz.Commands ( -- * The different Graphviz tools available. GraphvizCommand(..) , dirCommand , undirCommand , commandFor -- * The possible outputs that Graphviz supports. -- $outputs , GraphvizOutput(..) , GraphvizCanvas(..) -- * Running Graphviz. , runGraphviz , runGraphvizCommand , addExtension , runGraphvizCanvas , runGraphvizCanvas' , graphvizWithHandle -- * Testing if Graphviz is installed , isGraphvizInstalled , quitWithoutGraphviz ) where import Data.GraphViz.Types -- This is here just for Haddock linking purposes. import Data.GraphViz.Commands.Available import Data.GraphViz.Commands.IO (runCommand) import Data.GraphViz.Exception import Control.Monad (liftM, unless) import qualified Data.ByteString as SB import Data.Maybe (isJust) import Data.Version (Version (..), showVersion) import System.Directory (findExecutable) import System.Exit (ExitCode (..), exitWith) import System.FilePath ((<.>)) import System.IO (Handle, hPutStrLn, hSetBinaryMode, stderr) -- ----------------------------------------------------------------------------- showCmd :: GraphvizCommand -> String showCmd Dot = "dot" showCmd Neato = "neato" showCmd TwoPi = "twopi" showCmd Circo = "circo" showCmd Fdp = "fdp" showCmd Sfdp = "sfdp" showCmd Osage = "osage" showCmd Patchwork = "patchwork" -- | The default command for directed graphs. dirCommand :: GraphvizCommand dirCommand = Dot -- | The default command for undirected graphs. undirCommand :: GraphvizCommand undirCommand = Neato -- | The appropriate (default) Graphviz command for the given graph. commandFor :: (DotRepr dg n) => dg n -> GraphvizCommand commandFor dg = if graphIsDirected dg then dirCommand else undirCommand -- ----------------------------------------------------------------------------- {- $outputs The list of output types supported by Graphviz is dependent upon how it is built on your system. To determine which actual formats are available on your system, run @dot -T?@. Trying to use an output type that is not supported by your installation of Graphviz will result in an error. The outputs defined here in 'GraphvizOutput' and 'GraphvizCanvas' are those from the default list of available outputs. For more information, see: -} -- | This class is for those data types that are valid options for the -- Graphviz tools to use with the @-T@ argument. class GraphvizResult o where outputCall :: o -> String -- | The possible Graphviz output formats (that is, those that -- actually produce a file). data GraphvizOutput = Bmp -- ^ Windows Bitmap Format. | Canon -- ^ Pretty-printed Dot output with no -- layout performed. | DotOutput -- ^ Reproduces the input along with -- layout information. | XDot (Maybe Version) -- ^ As with 'DotOutput', but provides even more -- information on how the graph is drawn. The -- optional 'Version' is the same as -- specifying the @XDotVersion@ attribute. | Eps -- ^ Encapsulated PostScript. | Fig -- ^ FIG graphics language. | Gd -- ^ Internal GD library format. | Gd2 -- ^ Compressed version of 'Gd'. | Gif -- ^ Graphics Interchange Format. | Ico -- ^ Icon image file format. | Imap -- ^ Server-side imagemap. | Cmapx -- ^ Client-side imagemap. | ImapNP -- ^ As for 'Imap', except only -- rectangles are used as active -- areas. | CmapxNP -- ^ As for 'Cmapx', except only -- rectangles are used as active -- areas. | Jpeg -- ^ The JPEG image format. | Pdf -- ^ Portable Document Format. | Plain -- ^ Simple text format. | PlainExt -- ^ As for 'Plain', but provides port -- names on head and tail nodes when -- applicable. | Png -- ^ Portable Network Graphics format. | Ps -- ^ PostScript. | Ps2 -- ^ PostScript for PDF. | Svg -- ^ Scalable Vector Graphics format. | SvgZ -- ^ Compressed SVG format. | Tiff -- ^ Tagged Image File Format. | Vml -- ^ Vector Markup Language; 'Svg' is -- usually preferred. | VmlZ -- ^ Compressed VML format; 'SvgZ' is -- usually preferred. | Vrml -- ^ Virtual Reality Modeling Language -- format; requires nodes to have a -- third dimension set via the @Pos@ -- attribute (and with a @Dim@ value -- of at least @3@). | WBmp -- ^ Wireless BitMap format; -- monochrome format usually used -- for mobile computing devices. | WebP -- ^ Google's WebP format; requires -- Graphviz >= 2.29.0. deriving (Eq, Ord, Show, Read) instance GraphvizResult GraphvizOutput where outputCall Bmp = "bmp" outputCall Canon = "canon" outputCall DotOutput = "dot" outputCall (XDot mv) = "xdot" ++ maybe "" showVersion mv outputCall Eps = "eps" outputCall Fig = "fig" outputCall Gd = "gd" outputCall Gd2 = "gd2" outputCall Gif = "gif" outputCall Ico = "ico" outputCall Imap = "imap" outputCall Cmapx = "cmapx" outputCall ImapNP = "imap_np" outputCall CmapxNP = "cmapx_np" outputCall Jpeg = "jpeg" outputCall Pdf = "pdf" outputCall Plain = "plain" outputCall PlainExt = "plain-ext" outputCall Png = "png" outputCall Ps = "ps" outputCall Ps2 = "ps2" outputCall Svg = "svg" outputCall SvgZ = "svgz" outputCall Tiff = "tiff" outputCall Vml = "vml" outputCall VmlZ = "vmlz" outputCall Vrml = "vrml" outputCall WBmp = "wbmp" outputCall WebP = "webp" -- | A default file extension for each 'GraphvizOutput'. defaultExtension :: GraphvizOutput -> String defaultExtension Bmp = "bmp" defaultExtension Canon = "gv" defaultExtension DotOutput = "gv" defaultExtension XDot{} = "gv" defaultExtension Eps = "eps" defaultExtension Fig = "fig" defaultExtension Gd = "gd" defaultExtension Gd2 = "gd2" defaultExtension Gif = "gif" defaultExtension Ico = "ico" defaultExtension Imap = "map" defaultExtension Cmapx = "map" defaultExtension ImapNP = "map" defaultExtension CmapxNP = "map" defaultExtension Jpeg = "jpg" defaultExtension Pdf = "pdf" defaultExtension Plain = "txt" defaultExtension PlainExt = "txt" defaultExtension Png = "png" defaultExtension Ps = "ps" defaultExtension Ps2 = "ps" defaultExtension Svg = "svg" defaultExtension SvgZ = "svgz" defaultExtension Tiff = "tif" defaultExtension Vml = "vml" defaultExtension VmlZ = "vmlz" defaultExtension Vrml = "vrml" defaultExtension WBmp = "wbmp" defaultExtension WebP = "webp" -- | Unlike 'GraphvizOutput', these items do not produce an output -- file; instead, they directly draw a canvas (i.e. a window) with -- the resulting image. data GraphvizCanvas = Gtk | Xlib deriving (Eq, Ord, Bounded, Enum, Read, Show) instance GraphvizResult GraphvizCanvas where outputCall Gtk = "gtk" outputCall Xlib = "xlib" -- ----------------------------------------------------------------------------- -- | Run the recommended Graphviz command on this graph, saving the result -- to the file provided (note: file extensions are /not/ checked). runGraphviz :: (PrintDotRepr dg n) => dg n -> GraphvizOutput -> FilePath -> IO FilePath runGraphviz gr = runGraphvizCommand (commandFor gr) gr -- | Run the chosen Graphviz command on this graph, saving the result -- to the file provided (note: file extensions are /not/ checked). runGraphvizCommand :: (PrintDotRepr dg n) => GraphvizCommand -> dg n -> GraphvizOutput -> FilePath -> IO FilePath runGraphvizCommand cmd gr t fp = handle (throwIO . addExc) $ graphvizWithHandle cmd gr t toFile where addFl = (++) ("Unable to create " ++ fp ++ "\n") toFile h = SB.hGetContents h >>= SB.writeFile fp >> return fp addExc (GVProgramExc e) = GVProgramExc $ addFl e addExc e = e -- | Append the default extension for the provided 'GraphvizOutput' to -- the provided 'FilePath' for the output file. addExtension :: (GraphvizOutput -> FilePath -> a) -> GraphvizOutput -> FilePath -> a addExtension cmd t fp = cmd t fp' where fp' = fp <.> defaultExtension t -- | Run the chosen Graphviz command on this graph, but send the -- result to the given handle rather than to a file. -- -- Note that the @'Handle' -> 'IO' a@ function /must/ fully consume -- the input from the 'Handle'; e.g. use strict @ByteStrings@ rather -- than lazy ones. -- -- If the command was unsuccessful, then a 'GraphvizException' is -- thrown. graphvizWithHandle :: (PrintDotRepr dg n) => GraphvizCommand -- ^ Which command to run -> dg n -- ^ The 'DotRepr' to use -> GraphvizOutput -- ^ The 'GraphvizOutput' type -> (Handle -> IO a) -- ^ Extract the output -> IO a -- ^ The error or the result. graphvizWithHandle = graphvizWithHandle' -- This version is not exported as we don't want to let arbitrary -- @Handle -> IO a@ functions to be used for GraphvizCanvas outputs. graphvizWithHandle' :: (PrintDotRepr dg n, GraphvizResult o) => GraphvizCommand -> dg n -> o -> (Handle -> IO a) -> IO a graphvizWithHandle' cmd dg t f = runCommand (showCmd cmd) ["-T" ++ outputCall t] f' dg where f' h = hSetBinaryMode h True >> f h -- | Run the chosen Graphviz command on this graph and render it using -- the given canvas type. runGraphvizCanvas :: (PrintDotRepr dg n) => GraphvizCommand -> dg n -> GraphvizCanvas -> IO () runGraphvizCanvas cmd gr c = graphvizWithHandle' cmd gr c nullHandle where nullHandle :: Handle -> IO () nullHandle = liftM (const ()) . SB.hGetContents -- | Run the recommended Graphviz command on this graph and render it -- using the given canvas type. runGraphvizCanvas' :: (PrintDotRepr dg n) => dg n -> GraphvizCanvas -> IO () runGraphvizCanvas' d = runGraphvizCanvas (commandFor d) d -- ----------------------------------------------------------------------------- -- | Is the Graphviz suite of tools installed? This is determined by -- whether @dot@ is available in the @PATH@. isGraphvizInstalled :: IO Bool isGraphvizInstalled = liftM isJust . findExecutable $ showCmd Dot -- | If Graphviz does not seem to be available, print the provided -- error message and then exit fatally. quitWithoutGraphviz :: String -> IO () quitWithoutGraphviz err = do hasGraphviz <- isGraphvizInstalled unless hasGraphviz $ hPutStrLn stderr err >> exitWith (ExitFailure 1) graphviz-2999.20.2.0/Data/GraphViz/Commands/IO.hs0000644000000000000000000001767014535166704017263 0ustar0000000000000000{-# LANGUAGE MultiParamTypeClasses #-} {- | Module : Data.GraphViz.Commands.IO Description : IO-related functions for graphviz. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com Various utility functions to help with custom I\/O of Dot code. -} module Data.GraphViz.Commands.IO ( -- * Encoding -- $encoding toUTF8 -- * Operations on files , writeDotFile , readDotFile -- * Operations on handles , hPutDot , hPutCompactDot , hGetDot , hGetStrict -- * Special cases for standard input and output , putDot , readDot -- * Running external commands , runCommand ) where import Data.GraphViz.Exception import Data.GraphViz.Printing (runDotCode, toDot) import Data.GraphViz.Types (ParseDotRepr, PrintDotRepr, parseDotGraph, printDotGraph) import Text.PrettyPrint.Leijen.Text (displayT, renderOneLine) import Control.Concurrent (MVar, forkIO, newEmptyMVar, putMVar, takeMVar) import Control.Exception (IOException, evaluate, finally) import Control.Monad (liftM) import qualified Data.ByteString as SB import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as B import Data.Text.Encoding.Error (UnicodeException) import Data.Text.Lazy (Text) import qualified Data.Text.Lazy.Encoding as T import System.Exit (ExitCode(ExitSuccess)) import System.FilePath ((<.>)) import System.IO (Handle, IOMode(ReadMode, WriteMode), hClose, hGetContents, hPutChar, stdin, stdout, withFile) import System.IO.Temp (withSystemTempFile) import System.Process (runInteractiveProcess, waitForProcess) -- ----------------------------------------------------------------------------- -- | Correctly render Graphviz output in a more machine-oriented form -- (i.e. more compact than the output of 'renderDot'). renderCompactDot :: (PrintDotRepr dg n) => dg n -> Text renderCompactDot = displayT . renderOneLine . runDotCode . toDot -- ----------------------------------------------------------------------------- -- Encoding {- $encoding By default, Dot code should be in UTF-8. However, by usage of the /charset/ attribute, users are able to specify that the ISO-8859-1 (aka Latin1) encoding should be used instead: To simplify matters, graphviz does /not/ work with ISO-8859-1. If you wish to deal with existing Dot code that uses this encoding, you will need to manually read that file in to a 'Text' value. If a non-UTF-8 encoding is used, then a 'GraphvizException' will be thrown. -} -- | Explicitly convert a (lazy) 'ByteString' to a 'Text' value using -- UTF-8 encoding, throwing a 'GraphvizException' if there is a -- decoding error. toUTF8 :: ByteString -> Text toUTF8 = mapException fE . T.decodeUtf8 where fE :: UnicodeException -> GraphvizException fE e = NotUTF8Dot $ show e -- ----------------------------------------------------------------------------- -- Low-level Input/Output -- | Output the @DotRepr@ to the specified 'Handle'. hPutDot :: (PrintDotRepr dg n) => Handle -> dg n -> IO () hPutDot = toHandle printDotGraph -- | Output the @DotRepr@ to the spcified 'Handle' in a more compact, -- machine-oriented form. hPutCompactDot :: (PrintDotRepr dg n) => Handle -> dg n -> IO () hPutCompactDot = toHandle renderCompactDot toHandle :: (dg n -> Text) -> Handle -> dg n -> IO () toHandle f h dg = do B.hPutStr h . T.encodeUtf8 $ f dg hPutChar h '\n' -- | Strictly read in a 'Text' value using an appropriate encoding. hGetStrict :: Handle -> IO Text hGetStrict = liftM (toUTF8 . B.fromChunks . (:[])) . SB.hGetContents -- | Read in and parse a @DotRepr@ value from the specified 'Handle'. hGetDot :: (ParseDotRepr dg n) => Handle -> IO (dg n) hGetDot = liftM parseDotGraph . hGetStrict -- | Write the specified @DotRepr@ to file. writeDotFile :: (PrintDotRepr dg n) => FilePath -> dg n -> IO () writeDotFile f = withFile f WriteMode . flip hPutDot -- | Read in and parse a @DotRepr@ value from a file. readDotFile :: (ParseDotRepr dg n) => FilePath -> IO (dg n) readDotFile f = withFile f ReadMode hGetDot -- | Print the specified @DotRepr@ to 'stdout'. putDot :: (PrintDotRepr dg n) => dg n -> IO () putDot = hPutDot stdout -- | Read in and parse a @DotRepr@ value from 'stdin'. readDot :: (ParseDotRepr dg n) => IO (dg n) readDot = hGetDot stdin -- ----------------------------------------------------------------------------- -- | Run an external command on the specified @DotRepr@. Remember to -- use 'hSetBinaryMode' on the 'Handle' for the output function if -- necessary. -- -- If the command was unsuccessful, then a 'GraphvizException' is -- thrown. -- -- For performance reasons, a temporary file is used to store the -- generated Dot code. As such, this is only suitable for local -- commands. runCommand :: (PrintDotRepr dg n) => String -- ^ Command to run -> [String] -- ^ Command-line arguments -> (Handle -> IO a) -- ^ Obtaining the output; should be strict. -> dg n -> IO a runCommand cmd args hf dg = handle (throwIO . notRunnable) $ withSystemTempFile ("graphviz" <.> "gv") $ \dotFile dotHandle -> do finally (hPutCompactDot dotHandle dg) (hClose dotHandle) bracket (runInteractiveProcess cmd (args ++ [dotFile]) Nothing Nothing) (\(inh,outh,errh,_) -> hClose inh >> hClose outh >> hClose errh) $ \(inp,outp,errp,prc) -> do -- Not using it, so close it off directly. hClose inp -- Need to make sure both the output and error handles are -- really fully consumed. mvOutput <- newEmptyMVar mvErr <- newEmptyMVar forkIO $ signalWhenDone hGetContents' errp mvErr forkIO $ signalWhenDone hf' outp mvOutput -- When these are both able to be taken, then the forks are finished err <- takeMVar mvErr output <- takeMVar mvOutput exitCode <- waitForProcess prc case exitCode of ExitSuccess -> return output _ -> throw . GVProgramExc $ othErr ++ err where notRunnable :: IOException -> GraphvizException notRunnable e = GVProgramExc $ unwords [ "Unable to call the command " , cmd , " with the arguments: \"" , unwords args , "\" because of: " , show e ] -- Augmenting the hf function to let it work within the forkIO: hf' = handle (throwIO . fErr) . hf fErr :: IOException -> GraphvizException fErr e = GVProgramExc $ "Error re-directing the output from " ++ cmd ++ ": " ++ show e othErr = "Error messages from " ++ cmd ++ ":\n" -- ----------------------------------------------------------------------------- -- Utility functions -- | A version of 'hGetContents' that fully evaluates the contents of -- the 'Handle' (that is, until EOF is reached). The 'Handle' is -- not closed. hGetContents' :: Handle -> IO String hGetContents' h = do r <- hGetContents h evaluate $ length r return r -- | Store the result of the 'Handle' consumption into the 'MVar'. signalWhenDone :: (Handle -> IO a) -> Handle -> MVar a -> IO () signalWhenDone f h mv = f h >>= putMVar mv >> return () graphviz-2999.20.2.0/Data/GraphViz/Attributes.hs0000644000000000000000000003050414535166704017330 0ustar0000000000000000{-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-} {- | Module : Data.GraphViz.Attributes Description : User-friendly wrappers around Graphviz attributes. Copyright : (c) Matthew Sackman, Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com There are almost 150 possible attributes available for Dot graphs, and it can be difficult to know which ones to use. This module provides helper functions for the most commonly used ones. The complete list of all possible attributes can be found in "Data.GraphViz.Attributes.Complete"; it is possible to use both of these modules if you require specific extra attributes that are not provided here. -} module Data.GraphViz.Attributes ( -- * The definition of attributes Attribute , Attributes -- * Creating labels -- $labels , toLabel , textLabel , xLabel , xTextLabel , forceLabels , textLabelValue , Labellable(..) -- * Colors -- $colors , X11Color(..) , bgColor , bgColors , fillColor , fillColors , fontColor , penColor , color -- * Stylistic attributes -- $styles , penWidth , gradientAngle , style , styles , Style , dashed , dotted , solid , bold , invis , filled , diagonals , striped , wedged , rounded , tapered , radial -- * Node shapes , shape , Shape(..) -- * Edge arrows , arrowTo , arrowFrom -- ** Specifying where to draw arrows on an edge. , edgeEnds , DirType(..) -- ** Default arrow types. , Arrow -- *** The 9 primitive arrows. , box , crow , diamond , dotArrow , inv , noArrow , normal , tee , vee -- *** 5 derived arrows. , oDot , invDot , invODot , oBox , oDiamond -- * Layout , ordering , Order(..) , rank , RankType(..) ) where import Data.GraphViz.Attributes.Arrows import Data.GraphViz.Attributes.Colors import Data.GraphViz.Attributes.Colors.X11 import Data.GraphViz.Attributes.Complete (Attribute (..), Attributes) import qualified Data.GraphViz.Attributes.HTML as Html import Data.GraphViz.Attributes.Internal import Data.GraphViz.Attributes.Values import qualified Data.Text as ST import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T -- ----------------------------------------------------------------------------- {- $labels The following escape codes are available for labels (where applicable): [@\\N@] Replace with the name of the node. [@\\G@] Replace with the name of the graph (for node attributes) or the name of the graph or cluster, whichever is applicable (for graph, cluster and edge attributes). [@\\E@] Replace with the name of the edge, formed by the two adjoining nodes and the edge type. [@\\T@] Replace with the name of the node the edge is coming from. [@\\H@] Replace with the name of the node the edge is going to. [@\\n@] Centered newline. [@\\l@] Left-justified newline. [@\\r@] Right-justified newline. -} -- | A convenience class to make it easier to create labels. It is -- highly recommended that you make any other types that you wish to -- create labels from an instance of this class, preferably via the -- @String@ or @Text@ instances. class Labellable a where -- | This function only creates a 'Label' value to enable you to use -- it for 'Attributes' such as 'HeadLabel', etc. toLabelValue :: a -> Label -- | Equivalent to @'Label' . 'toLabelValue'@; the most common label -- 'Attribute'. toLabel :: (Labellable a) => a -> Attribute toLabel = Label . toLabelValue -- | An alias for 'toLabel' for use with the @OverloadedStrings@ -- extension. textLabel :: Text -> Attribute textLabel = toLabel -- | Create a label /outside/ of a node\/edge. Currently only in the -- Graphviz development branch (2.29.*). xLabel :: (Labellable a) => a -> Attribute xLabel = XLabel . toLabelValue -- | An alias for 'xLabel' for use with the @OverloadedStrings@ extension. xTextLabel :: Text -> Attribute xTextLabel = xLabel -- | Force the positioning of 'xLabel's, even when it will cause overlaps. forceLabels :: Attribute forceLabels = ForceLabels True -- | An alias for 'toLabelValue' for use with the @OverloadedStrings@ -- extension. textLabelValue :: Text -> Label textLabelValue = toLabelValue instance Labellable Text where toLabelValue = StrLabel instance Labellable ST.Text where toLabelValue = toLabelValue . T.fromStrict instance Labellable Char where toLabelValue = toLabelValue . T.singleton instance Labellable String where toLabelValue = toLabelValue . T.pack instance Labellable Int where toLabelValue = toLabelValue . show instance Labellable Double where toLabelValue = toLabelValue . show instance Labellable Bool where toLabelValue = toLabelValue . show instance Labellable Html.Label where toLabelValue = HtmlLabel instance Labellable Html.Text where toLabelValue = toLabelValue . Html.Text instance Labellable Html.Table where toLabelValue = toLabelValue . Html.Table instance Labellable RecordFields where toLabelValue = RecordLabel instance Labellable RecordField where toLabelValue = toLabelValue . (:[]) -- | A shorter variant than using @PortName@ from 'RecordField'. instance Labellable PortName where toLabelValue = toLabelValue . PortName -- | A shorter variant than using 'LabelledTarget'. instance Labellable (PortName, EscString) where toLabelValue = toLabelValue . uncurry LabelledTarget -- ----------------------------------------------------------------------------- {- $colors The recommended way of dealing with colors in Dot graphs is to use the named 'X11Color's rather than explicitly specifying RGB, RGBA or HSV colors. These functions also allow you to use SVG and Brewer colors, but X11 colors are generally preferable. If you wish to use SVG colors, either import this module hiding 'X11Color' or import the SVG module qualified. -} -- | Specify the background color of a graph or cluster. For -- clusters, if @'style' 'filled'@ is used, then 'fillColor' will -- override it. bgColor :: (NamedColor nc) => nc -> Attribute bgColor = BgColor . toColorList . (:[]) . toColor -- | As with 'bgColor', but add a second color to create a gradient -- effect. Requires Graphviz >= 2.29.0. bgColors :: (NamedColor nc) => nc -> nc -> Attribute bgColors c1 c2 = BgColor . toColorList $ map toColor [c1,c2] -- | Specify the fill color of a node, cluster or arrowhead. Requires -- @'style' 'filled'@ for nodes and clusters. For nodes and edges, -- if this isn't set then the 'color' value is used instead; for -- clusters, 'bgColor' is used. fillColor :: (NamedColor nc) => nc -> Attribute fillColor = FillColor . toColorList . (:[]) . toColor -- | As with 'fillColor', but add a second color to create a gradient -- effect. Requires Graphviz >= 2.29.0. fillColors :: (NamedColor nc) => nc -> nc -> Attribute fillColors c1 c2 = FillColor . toColorList $ map toColor [c1,c2] -- | Specify the color of text. fontColor :: (NamedColor nc) => nc -> Attribute fontColor = FontColor . toColor -- | Specify the color of the bounding box of a cluster. penColor :: (NamedColor nc) => nc -> Attribute penColor = PenColor . toColor -- | The @color@ attribute serves several purposes. As such care must -- be taken when using it, and it is preferable to use those -- alternatives that are available when they exist. -- -- * The color of edges; -- -- * The bounding color of nodes; -- -- * The bounding color of clusters (i.e. equivalent to 'penColor'); -- -- * If the 'filled' 'Style' is set, then it defines the -- background color of nodes and clusters unless 'fillColor' or -- 'bgColor' respectively is set. color :: (NamedColor nc) => nc -> Attribute color = Color . toColorList . (:[]) . toColor -- ----------------------------------------------------------------------------- {- $styles Various stylistic attributes to customise how items are drawn. Unless specified otherwise, all 'Style's are available for nodes; those specified also can be used for edges and clusters. -} -- | A particular style type to be used. type Style = StyleItem style :: Style -> Attribute style = styles . (:[]) styles :: [Style] -> Attribute styles = Style -- | Also available for edges. dashed :: Style dashed = SItem Dashed [] -- | Also available for edges. dotted :: Style dotted = SItem Dotted [] -- | Also available for edges. solid :: Style solid = SItem Solid [] -- | Also available for edges. invis :: Style invis = SItem Invisible [] -- | Also available for edges. bold :: Style bold = SItem Bold [] -- | Also available for clusters. filled :: Style filled = SItem Filled [] -- | Also available for clusters. rounded :: Style rounded = SItem Rounded [] -- | Only available for nodes. diagonals :: Style diagonals = SItem Diagonals [] -- | Only available for rectangularly-shaped nodes and -- clusters. Requires Graphviz >= 2.30.0. striped :: Style striped = SItem Striped [] -- | Only available for elliptically-shaped nodes. Requires Graphviz -- >= 2.30.0. wedged :: Style wedged = SItem Wedged [] -- | Only available for edges; creates a tapered edge between the two -- nodes. Requires Graphviz >= 2.29.0. tapered :: Style tapered = SItem Tapered [] -- | Available for nodes, clusters and edges. When using -- 'gradientAngle', indicates that a radial gradient should be used. -- Requires Graphviz >= 2.29.0. radial :: Style radial = SItem Radial [] -- | Specify the width of lines. Valid for clusters, nodes and edges. penWidth :: Double -> Attribute penWidth = PenWidth -- | Specify the angle at which gradient fills are drawn; for use with -- 'bgColors' and 'fillColors'. Requires Graphviz >= 2.29.0. gradientAngle :: Int -> Attribute gradientAngle = GradientAngle -- ----------------------------------------------------------------------------- -- | The shape of a node. shape :: Shape -> Attribute shape = Shape -- ----------------------------------------------------------------------------- -- | A particular way of drawing the end of an edge. type Arrow = ArrowType -- | How to draw the arrow at the node the edge is pointing to. For -- an undirected graph, requires either @'edgeEnds' 'Forward'@ or -- @'edgeEnds' 'Both'@. arrowTo :: Arrow -> Attribute arrowTo = ArrowHead -- | How to draw the arrow at the node the edge is coming from. -- Requires either @'edgeEnds' 'Back'@ or @'edgeEnds' 'Both'@. arrowFrom :: Arrow -> Attribute arrowFrom = ArrowTail -- | Specify where to place arrows on an edge. edgeEnds :: DirType -> Attribute edgeEnds = Dir box, crow, diamond, dotArrow, inv, noArrow, tee, vee :: Arrow oDot, invDot, invODot, oBox, oDiamond :: Arrow inv = AType [(noMods, Inv)] dotArrow = AType [(noMods, DotArrow)] invDot = AType [ (noMods, Inv) , (noMods, DotArrow)] oDot = AType [(ArrMod OpenArrow BothSides, DotArrow)] invODot = AType [ (noMods, Inv) , (openMod, DotArrow)] noArrow = AType [(noMods, NoArrow)] tee = AType [(noMods, Tee)] diamond = AType [(noMods, Diamond)] oDiamond = AType [(openMod, Diamond)] crow = AType [(noMods, Crow)] box = AType [(noMods, Box)] oBox = AType [(openMod, Box)] vee = AType [(noMods, Vee)] -- ----------------------------------------------------------------------------- -- | Specify an ordering of edges of a node: either the outgoing or -- the incoming edges of a node must appear left-to-right in the -- same order in which they are defined in the input. -- -- When specified as both a global graph or sub-graph level -- attribute, then it takes precedence over an attribute specified -- for an individual node. ordering :: Order -> Attribute ordering = Ordering -- ----------------------------------------------------------------------------- -- | When using @dot@, this allows you to control relative placement -- of sub-graphs and clusters. rank :: RankType -> Attribute rank = Rank graphviz-2999.20.2.0/Data/GraphViz/Attributes/Complete.hs0000644000000000000000000025200314535166704021100 0ustar0000000000000000{-# 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: 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 (Eq, Ord, Show, Read) type Attributes = [Attribute] -- | The name for an UnknownAttribute; must satisfy 'validUnknown'. 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 (Background v) = printField "_background" 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 (InputScale v) = printField "inputscale" 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 (NoTranslate v) = printField "notranslate" 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 (OverlapShrink v) = printField "overlap_shrink" 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 (XDotVersion v) = printField "xdotversion" 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 Background "_background" , 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" , parseFieldDef FixedSize SetNodeSize "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 InputScale "inputscale" , 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" , parseFieldDef Normalize IsNormalized "normalize" , parseFieldBool NoTranslate "notranslate" , parseField Nslimit "nslimit" , parseField Nslimit1 "nslimit1" , parseField Ordering "ordering" , parseField Orientation "orientation" , parseField OutputOrder "outputorder" , parseFieldDef Overlap KeepOverlaps "overlap" , parseField OverlapScaling "overlap_scaling" , parseFieldBool OverlapShrink "overlap_shrink" , 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 XDotVersion "xdotversion" , parseField XLabel "xlabel" , parseField XLP "xlp" ]) `onFail` do attrName <- stringBlock liftEqParse ("UnknownAttribute (" ++ T.unpack attrName ++ ")") (UnknownAttribute attrName) parse = parseUnqt parseList = parseUnqtList -- | Determine if this 'Attribute' is valid for use with Graphs. usedByGraphs :: Attribute -> Bool usedByGraphs Damping{} = True usedByGraphs K{} = True usedByGraphs URL{} = True usedByGraphs Background{} = 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 NoTranslate{} = True usedByGraphs Nslimit{} = True usedByGraphs Nslimit1{} = True usedByGraphs Ordering{} = True usedByGraphs OutputOrder{} = True usedByGraphs Overlap{} = True usedByGraphs OverlapScaling{} = True usedByGraphs OverlapShrink{} = 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 Style{} = True usedByGraphs StyleSheet{} = True usedByGraphs Target{} = True usedByGraphs TrueColor{} = True usedByGraphs ViewPort{} = True usedByGraphs VoroMargin{} = True usedByGraphs XDotVersion{} = True usedByGraphs UnknownAttribute{} = True usedByGraphs _ = False -- | Determine if this 'Attribute' is valid for use with Clusters. 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 Layer{} = True usedByClusters LHeight{} = True usedByClusters LPos{} = True usedByClusters LWidth{} = True usedByClusters Margin{} = 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 -- | Determine if this 'Attribute' is valid for use with SubGraphs. usedBySubGraphs :: Attribute -> Bool usedBySubGraphs Rank{} = True usedBySubGraphs UnknownAttribute{} = True usedBySubGraphs _ = False -- | Determine if this 'Attribute' is valid for use with Nodes. 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 InputScale{} = 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 -- | Determine if this 'Attribute' is valid for use with Edges. 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 -- | Determine if two 'Attributes' are the same type of 'Attribute'. 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 Background{} Background{} = 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 InputScale{} InputScale{} = 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 NoTranslate{} NoTranslate{} = 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 OverlapShrink{} OverlapShrink{} = 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 XDotVersion{} XDotVersion{} = True sameAttribute XLabel{} XLabel{} = True sameAttribute XLP{} XLP{} = True sameAttribute (UnknownAttribute a1 _) (UnknownAttribute a2 _) = a1 == a2 sameAttribute _ _ = 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 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 Background{} = Just $ Background "" 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 GrowAsNeeded 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 NotNormalized defaultAttributeValue NoTranslate{} = Just $ NoTranslate False defaultAttributeValue Orientation{} = Just $ Orientation 0.0 defaultAttributeValue OutputOrder{} = Just $ OutputOrder BreadthFirst defaultAttributeValue Overlap{} = Just $ Overlap KeepOverlaps defaultAttributeValue OverlapScaling{} = Just $ OverlapScaling (-4) defaultAttributeValue OverlapShrink{} = Just $ OverlapShrink True 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 (Int 1) defaultAttributeValue Width{} = Just $ Width 0.75 defaultAttributeValue XLabel{} = Just $ XLabel (StrLabel "") defaultAttributeValue _ = Nothing -- | Determine if the provided 'Text' value is a valid name for an 'UnknownAttribute'. 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" , "_background" , "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" , "inputscale" , "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" , "notranslate" , "nslimit" , "nslimit1" , "ordering" , "orientation" , "outputorder" , "overlap" , "overlap_scaling" , "overlap_shrink" , "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" , "xdotversion" , "xlabel" , "xlp" , "charset" -- Defined upstream, just not used here. ]) `S.union` 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 = filter (not . (`any` tests) . flip ($)) where tests = [isDefault, isColorScheme] isDefault a = maybe False (a==) $ defaultAttributeValue a isColorScheme ColorScheme{} = True isColorScheme _ = False -- ----------------------------------------------------------------------------- -- These parsing combinators are defined here for customisation purposes. 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) -- | 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 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) -- | 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 k c = do pStrict <- getsGS parseStrictly let adjErr = bool adjustErr adjustErrBad pStrict parseEq *> ( hasDef (fmap c parse) `adjErr` (("Unable to parse key=value with key of " ++ k ++ "\n\t") ++) ) where hasDef p = maybe p (onFail p . (`stringRep` "\"\"")) . defaultAttributeValue $ c 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 = UnknownAttribute -- | Determines whether or not this is a custom attribute. isCustom :: Attribute -> Bool isCustom UnknownAttribute{} = True isCustom _ = False isSpecifiedCustom :: AttributeName -> Attribute -> Bool isSpecifiedCustom nm (UnknownAttribute nm' _) = nm == nm' isSpecifiedCustom _ _ = False -- | The value of a custom attribute. Will throw a -- 'GraphvizException' if the provided 'Attribute' isn't a custom -- one. customValue :: CustomAttribute -> Text customValue (UnknownAttribute _ v) = v customValue attr = throw . NotCustomAttr . T.unpack $ printIt attr -- | The name of a custom attribute. Will throw a -- 'GraphvizException' if the provided 'Attribute' isn't a custom -- one. customName :: CustomAttribute -> AttributeName customName (UnknownAttribute nm _) = nm customName attr = throw . NotCustomAttr . T.unpack $ printIt attr -- | Returns all custom attributes and the list of non-custom Attributes. findCustoms :: Attributes -> ([CustomAttribute], Attributes) findCustoms = partition 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 nm attrs = case break (isSpecifiedCustom nm) attrs of (bf,cust:aft) -> Just (cust, bf ++ aft) _ -> 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 = filter (not . isCustom) -- | Removes all instances of the specified custom attribute. deleteSpecifiedCustom :: AttributeName -> Attributes -> Attributes deleteSpecifiedCustom nm = filter (not . isSpecifiedCustom nm) graphviz-2999.20.2.0/Data/GraphViz/Attributes/Colors.hs0000644000000000000000000003236314535166704020576 0ustar0000000000000000{-# LANGUAGE CPP, OverloadedStrings #-} {- | Module : Data.GraphViz.Attributes.Colors Description : Specification of Color-related types and functions. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module defines the various colors, etc. for Graphviz. For information on colors in general, see: For named colors, see: Note that the ColorBrewer Color Schemes (shortened to just \"Brewer\" for the rest of this module) are covered by the following license (also available in the LICENSE file of this library): -} module Data.GraphViz.Attributes.Colors ( -- * Color schemes. ColorScheme(..) -- * Colors , Color(..) , ColorList , WeightedColor(..) , toWC , toColorList , NamedColor(toColor) , toWColor -- * Conversion to\/from @Colour@. , toColour , fromColour , fromAColour ) where import Data.GraphViz.Attributes.Colors.Brewer (BrewerColor(..)) import Data.GraphViz.Attributes.Colors.SVG (SVGColor, svgColour) import Data.GraphViz.Attributes.Colors.X11 (X11Color(Transparent), x11Colour) import Data.GraphViz.Attributes.ColorScheme (ColorScheme(..)) import Data.GraphViz.Exception import Data.GraphViz.Internal.State import Data.GraphViz.Internal.Util (bool) import Data.GraphViz.Parsing import Data.GraphViz.Printing import Data.Colour (AlphaColour, alphaChannel, black, darken, opaque, over, withOpacity) import Data.Colour.RGBSpace (uncurryRGB) import Data.Colour.RGBSpace.HSV (hsv) import Data.Colour.SRGB (Colour, sRGB, sRGB24, toSRGB24) import Data.Char (isHexDigit) import Data.Maybe (isJust) import qualified Data.Text.Lazy as T import Data.Word (Word8) import Numeric (readHex, showHex) #if !MIN_VERSION_base (4,13,0) import Data.Monoid ((<>)) #endif -- ----------------------------------------------------------------------------- -- | Defining a color for use with Graphviz. Note that named colors -- have been split up into 'X11Color's and those based upon the -- Brewer color schemes. data Color = RGB { red :: Word8 , green :: Word8 , blue :: Word8 } | RGBA { red :: Word8 , green :: Word8 , blue :: Word8 , alpha :: Word8 } -- | The 'hue', 'saturation' and 'value' values must all -- be @0 <= x <=1@. | HSV { hue :: Double , saturation :: Double , value :: Double } | X11Color X11Color | SVGColor SVGColor | BrewerColor BrewerColor deriving (Eq, Ord, Show, Read) instance PrintDot Color where unqtDot (RGB r g b) = hexColor [r,g,b] unqtDot (RGBA r g b a) = hexColor [r,g,b,a] unqtDot (HSV h s v) = hcat . punctuate comma $ mapM unqtDot [h,s,v] unqtDot (SVGColor name) = printNC False name unqtDot (X11Color name) = printNC False name unqtDot (BrewerColor bc) = printNC False bc -- Some cases might not need quotes. toDot (X11Color name) = printNC True name toDot (SVGColor name) = printNC True name toDot (BrewerColor bc) = printNC True bc toDot c = dquotes $ unqtDot c unqtListToDot = hcat . punctuate colon . mapM unqtDot -- These three might not need to be quoted if they're on their own. listToDot [X11Color name] = printNC True name listToDot [SVGColor name] = printNC True name listToDot [BrewerColor bc] = printNC True bc listToDot cs = dquotes $ unqtListToDot cs hexColor :: [Word8] -> DotCode hexColor = (<>) (char '#') . hcat . mapM word8Doc word8Doc :: Word8 -> DotCode word8Doc w = text $ padding `T.append` simple where simple = T.pack $ showHex w "" padding = T.replicate count (T.singleton '0') count = 2 - findCols 1 w findCols c n | n < 16 = c | otherwise = findCols (c+1) (n `div` 16) instance ParseDot Color where parseUnqt = oneOf [ parseHexBased , parseHSV -- Have to parse BrewerColor first, as some of them may appear to be X11 colors , parseNC (undefined :: BrewerColor) False , parseNC (undefined :: SVGColor) False , parseX11Color False ] `onFail` fail "Could not parse Color" where parseHexBased = character '#' *> do cs <- many1 parse2Hex return $ case cs of [r,g,b] -> RGB r g b [r,g,b,a] -> RGBA r g b a _ -> throw . NotDotCode $ "Not a valid hex Color specification: " ++ show cs parseHSV = HSV <$> parseUnqt <* parseSep <*> parseUnqt <* parseSep <*> parseUnqt parseSep = character ',' *> whitespace <|> whitespace1 parse2Hex = do c1 <- satisfy isHexDigit c2 <- satisfy isHexDigit let [(n, [])] = readHex [c1, c2] return n parse = quotedParse parseUnqt `onFail` -- These three might not need to be quoted oneOf [ parseNC (undefined :: BrewerColor) True , parseNC (undefined :: SVGColor) True , parseX11Color True ] `onFail` fail "Could not parse Color" parseUnqtList = sepBy1 parseUnqt (character ':') `onFail` do cs <- getColorScheme failBad $ "Error parsing list of Colors with color scheme of " ++ show cs parseList = fmap (:[]) -- Potentially unquoted single color (oneOf [ parseNC (undefined :: BrewerColor) True , parseNC (undefined :: SVGColor) True , parseX11Color True ] ) `onFail` quotedParse parseUnqtList `onFail` do cs <- getColorScheme failBad $ "Error parsing list of Colors with color scheme of " ++ show cs -- | The sum of the optional weightings /must/ sum to at most @1@. type ColorList = [WeightedColor] -- | A 'Color' tagged with an optional weighting. data WeightedColor = WC { wColor :: Color -- | Must be in range @0 <= W <= 1@. , weighting :: Maybe Double } deriving (Eq, Ord, Show, Read) -- | For colors without weightings. toWC :: Color -> WeightedColor toWC = (`WC` Nothing) -- | For a list of colors without weightings. toColorList :: [Color] -> ColorList toColorList = map toWC instance PrintDot WeightedColor where unqtDot (WC c mw) = unqtDot c <> maybe empty ((semi<>) . unqtDot) mw toDot (WC c Nothing) = toDot c toDot wc = dquotes $ unqtDot wc unqtListToDot = hcat . punctuate colon . mapM unqtDot -- Might not need quoting listToDot [wc] = toDot wc listToDot wcs = dquotes $ unqtListToDot wcs instance ParseDot WeightedColor where parseUnqt = WC <$> parseUnqt <*> optional (character ';' *> parseUnqt) parse = quotedParse parseUnqt `onFail` -- Using parse rather than parseUnqt as there shouldn't be -- any quotes, but to avoid copy-pasting the oneOf block. (toWC <$> parse) parseUnqtList = sepBy1 parseUnqt (character ':') `onFail` do cs <- getColorScheme failBad $ "Error parsing a ColorList with color scheme of " ++ show cs parseList = quotedParse parseUnqtList `onFail` ((:[]) . toWC <$> parse) -- Potentially unquoted un-weighted single color `onFail` do cs <- getColorScheme failBad $ "Error parsing ColorList with color scheme of " ++ show cs -- ----------------------------------------------------------------------------- -- | More easily convert named colors to an overall 'Color' value. class NamedColor nc where colorScheme :: nc -> ColorScheme toColor :: nc -> Color printNC :: Bool -> nc -> DotCode -- | Bool is for whether quoting is needed. parseNC' :: Bool -> Parse nc toWColor :: (NamedColor nc) => nc -> WeightedColor toWColor = toWC . toColor -- First value just used for type parseNC :: (NamedColor nc) => nc -> Bool -> Parse Color parseNC nc q = fmap (toColor . (`asTypeOf` nc)) $ parseNC' q instance NamedColor BrewerColor where colorScheme (BC bs _) = Brewer bs toColor = BrewerColor printNC = printNamedColor (\ (BC _ l) -> l) parseNC' = parseNamedColor mBCS parseUnqt (const True) BC where mBCS (Brewer bs) = Just bs mBCS _ = Nothing instance NamedColor X11Color where colorScheme = const X11 toColor = X11Color printNC = printNamedColor id parseNC' = parseNamedColor mX11 (parseColorScheme False) (isJust . mX11) (const id) where mX11 X11 = Just X11 mX11 _ = Nothing instance NamedColor SVGColor where colorScheme = const SVG toColor = SVGColor printNC = printNamedColor id parseNC' = parseNamedColor mSVG (parseColorScheme False) (isJust . mSVG) (const id) where mSVG SVG = Just SVG mSVG _ = Nothing printNamedColor :: (NamedColor nc, PrintDot lv) => (nc -> lv) -> Bool -> nc -> DotCode printNamedColor fl q c = do currentCS <- getColorScheme if cs == currentCS then (bool unqtDot toDot q) lv else bool id dquotes q $ fslash <> printColorScheme False cs <> fslash <> unqtDot lv where cs = colorScheme c lv = fl c parseNamedColor :: (ParseDot lv) => (ColorScheme -> Maybe cs) -> Parse cs -> (cs -> Bool) -> (cs -> lv -> nc) -> Bool -> Parse nc parseNamedColor gcs parseCS vcs mkC q = do Just cs <- gcs <$> getColorScheme lv <- bool parseUnqt parse q `onFail` mQts (string "//" *> parseUnqt) return $ mkC cs lv `onFail` mQts ( do character '/' cs <- parseCS character '/' if vcs cs then mkC cs <$> parseUnqt else fail "Explicit colorscheme not as expected." ) where mQts = bool id quotedParse q -- ----------------------------------------------------------------------------- -- X11 has a special case when parsing: '/yyyy' parseX11Color :: Bool -> Parse Color parseX11Color q = X11Color <$> parseNC' q `onFail` bool id quotedParse q (character '/' *> parseUnqt) `onFail` -- Can use X11 colors within brewer colorscheme. do cs <- getColorScheme case cs of Brewer{} -> bool parseUnqt parse q _ -> fail "Unable to parse an X11 color within Brewer" -- ----------------------------------------------------------------------------- -- | Attempt to convert a 'Color' into a 'Colour' value with an alpha -- channel. The use of 'Maybe' is because the RGB values of the -- 'BrewerColor's haven't been stored here (primarily for licensing -- reasons). toColour :: Color -> Maybe (AlphaColour Double) toColour (RGB r g b) = Just . opaque $ sRGB24 r g b toColour (RGBA r g b a) = Just . withOpacity (sRGB24 r g b) $ toOpacity a -- Colour expects the hue to be an angle, so multiply by 360 toColour (HSV h s v) = Just . opaque . uncurryRGB sRGB $ hsv (h*360) s v toColour (X11Color c) = Just $ x11Colour c toColour (SVGColor c) = Just . opaque $ svgColour c toColour BrewerColor{} = Nothing toOpacity :: Word8 -> Double toOpacity a = fromIntegral a / maxWord -- | Convert a 'Colour' value to an 'RGB' 'Color'. fromColour :: Colour Double -> Color fromColour = uncurryRGB RGB . toSRGB24 -- | Convert an 'AlphaColour' to an 'RGBA' 'Color'. The exception to -- this is for any 'AlphaColour' which has @alphaChannel ac == 0@; -- these are converted to @X11Color 'Transparent'@ (note that the -- 'Show' instance for such an 'AlphaColour' is @\"transparent\"@). fromAColour :: AlphaColour Double -> Color fromAColour ac | a == 0 = X11Color Transparent | otherwise = rgb $ round a' where a = alphaChannel ac a' = a * maxWord rgb = uncurryRGB RGBA $ toSRGB24 colour colour = darken (recip a) (ac `over` black) -- | The 'maxBound' of a 'Word8' value. maxWord :: Double maxWord = fromIntegral (maxBound :: Word8) graphviz-2999.20.2.0/Data/GraphViz/Attributes/Colors/X11.hs0000644000000000000000000033421514535166704021150 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {- | Module : Data.GraphViz.Attributes.Colors.X11 Description : Specification of X11 colors. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com Graphviz's definition of X11 colors differs from the \"normal\" list installed on many systems at @/usr/share/X11/rgb.txt@. For example, @Crimson@ is not a usual X11 color. Furthermore, all @Gray*@ colors are duplicated with @Grey*@ names. To simplify this, these duplicates have been removed but /all/ 'X11Color's with \"@Gray@\" (whether they have the duplicate spelling or not) in their name are also parseable as if they were spelt with \"@grey@\". The complete list of X11 colors can be found at . -} module Data.GraphViz.Attributes.Colors.X11 ( X11Color(..) , x11Colour ) where import Data.GraphViz.Parsing import Data.GraphViz.Printing import Data.Colour( AlphaColour, opaque, transparent) import Data.Colour.SRGB(sRGB24) -- ----------------------------------------------------------------------------- -- | The X11 colors that Graphviz uses. Note that these are slightly -- different from the \"normal\" X11 colors used (e.g. the inclusion -- of @Crimson@). Graphviz's list of colors also duplicated almost -- all @Gray@ colors with @Grey@ ones; parsing of an 'X11Color' -- which is specified using \"grey\" will succeed, even for those -- that don't have the duplicate spelling (e.g. @DarkSlateGray1@). data X11Color = AliceBlue | AntiqueWhite | AntiqueWhite1 | AntiqueWhite2 | AntiqueWhite3 | AntiqueWhite4 | Aquamarine | Aquamarine1 | Aquamarine2 | Aquamarine3 | Aquamarine4 | Azure | Azure1 | Azure2 | Azure3 | Azure4 | Beige | Bisque | Bisque1 | Bisque2 | Bisque3 | Bisque4 | Black | BlanchedAlmond | Blue | Blue1 | Blue2 | Blue3 | Blue4 | BlueViolet | Brown | Brown1 | Brown2 | Brown3 | Brown4 | Burlywood | Burlywood1 | Burlywood2 | Burlywood3 | Burlywood4 | CadetBlue | CadetBlue1 | CadetBlue2 | CadetBlue3 | CadetBlue4 | Chartreuse | Chartreuse1 | Chartreuse2 | Chartreuse3 | Chartreuse4 | Chocolate | Chocolate1 | Chocolate2 | Chocolate3 | Chocolate4 | Coral | Coral1 | Coral2 | Coral3 | Coral4 | CornFlowerBlue | CornSilk | CornSilk1 | CornSilk2 | CornSilk3 | CornSilk4 | Crimson | Cyan | Cyan1 | Cyan2 | Cyan3 | Cyan4 | DarkGoldenrod | DarkGoldenrod1 | DarkGoldenrod2 | DarkGoldenrod3 | DarkGoldenrod4 | DarkGreen | Darkkhaki | DarkOliveGreen | DarkOliveGreen1 | DarkOliveGreen2 | DarkOliveGreen3 | DarkOliveGreen4 | DarkOrange | DarkOrange1 | DarkOrange2 | DarkOrange3 | DarkOrange4 | DarkOrchid | DarkOrchid1 | DarkOrchid2 | DarkOrchid3 | DarkOrchid4 | DarkSalmon | DarkSeaGreen | DarkSeaGreen1 | DarkSeaGreen2 | DarkSeaGreen3 | DarkSeaGreen4 | DarkSlateBlue | DarkSlateGray | DarkSlateGray1 | DarkSlateGray2 | DarkSlateGray3 | DarkSlateGray4 | DarkTurquoise | DarkViolet | DeepPink | DeepPink1 | DeepPink2 | DeepPink3 | DeepPink4 | DeepSkyBlue | DeepSkyBlue1 | DeepSkyBlue2 | DeepSkyBlue3 | DeepSkyBlue4 | DimGray | DodgerBlue | DodgerBlue1 | DodgerBlue2 | DodgerBlue3 | DodgerBlue4 | Firebrick | Firebrick1 | Firebrick2 | Firebrick3 | Firebrick4 | FloralWhite | ForestGreen | Gainsboro | GhostWhite | Gold | Gold1 | Gold2 | Gold3 | Gold4 | Goldenrod | Goldenrod1 | Goldenrod2 | Goldenrod3 | Goldenrod4 | Gray | Gray0 | Gray1 | Gray2 | Gray3 | Gray4 | Gray5 | Gray6 | Gray7 | Gray8 | Gray9 | Gray10 | Gray11 | Gray12 | Gray13 | Gray14 | Gray15 | Gray16 | Gray17 | Gray18 | Gray19 | Gray20 | Gray21 | Gray22 | Gray23 | Gray24 | Gray25 | Gray26 | Gray27 | Gray28 | Gray29 | Gray30 | Gray31 | Gray32 | Gray33 | Gray34 | Gray35 | Gray36 | Gray37 | Gray38 | Gray39 | Gray40 | Gray41 | Gray42 | Gray43 | Gray44 | Gray45 | Gray46 | Gray47 | Gray48 | Gray49 | Gray50 | Gray51 | Gray52 | Gray53 | Gray54 | Gray55 | Gray56 | Gray57 | Gray58 | Gray59 | Gray60 | Gray61 | Gray62 | Gray63 | Gray64 | Gray65 | Gray66 | Gray67 | Gray68 | Gray69 | Gray70 | Gray71 | Gray72 | Gray73 | Gray74 | Gray75 | Gray76 | Gray77 | Gray78 | Gray79 | Gray80 | Gray81 | Gray82 | Gray83 | Gray84 | Gray85 | Gray86 | Gray87 | Gray88 | Gray89 | Gray90 | Gray91 | Gray92 | Gray93 | Gray94 | Gray95 | Gray96 | Gray97 | Gray98 | Gray99 | Gray100 | Green | Green1 | Green2 | Green3 | Green4 | GreenYellow | HoneyDew | HoneyDew1 | HoneyDew2 | HoneyDew3 | HoneyDew4 | HotPink | HotPink1 | HotPink2 | HotPink3 | HotPink4 | IndianRed | IndianRed1 | IndianRed2 | IndianRed3 | IndianRed4 | Indigo | Ivory | Ivory1 | Ivory2 | Ivory3 | Ivory4 | Khaki | Khaki1 | Khaki2 | Khaki3 | Khaki4 | Lavender | LavenderBlush | LavenderBlush1 | LavenderBlush2 | LavenderBlush3 | LavenderBlush4 | LawnGreen | LemonChiffon | LemonChiffon1 | LemonChiffon2 | LemonChiffon3 | LemonChiffon4 | LightBlue | LightBlue1 | LightBlue2 | LightBlue3 | LightBlue4 | LightCoral | LightCyan | LightCyan1 | LightCyan2 | LightCyan3 | LightCyan4 | LightGoldenrod | LightGoldenrod1 | LightGoldenrod2 | LightGoldenrod3 | LightGoldenrod4 | LightGoldenrodYellow | LightGray | LightPink | LightPink1 | LightPink2 | LightPink3 | LightPink4 | LightSalmon | LightSalmon1 | LightSalmon2 | LightSalmon3 | LightSalmon4 | LightSeaGreen | LightSkyBlue | LightSkyBlue1 | LightSkyBlue2 | LightSkyBlue3 | LightSkyBlue4 | LightSlateBlue | LightSlateGray | LightSteelBlue | LightSteelBlue1 | LightSteelBlue2 | LightSteelBlue3 | LightSteelBlue4 | LightYellow | LightYellow1 | LightYellow2 | LightYellow3 | LightYellow4 | LimeGreen | Linen | Magenta | Magenta1 | Magenta2 | Magenta3 | Magenta4 | Maroon | Maroon1 | Maroon2 | Maroon3 | Maroon4 | MediumAquamarine | MediumBlue | MediumOrchid | MediumOrchid1 | MediumOrchid2 | MediumOrchid3 | MediumOrchid4 | MediumPurple | MediumPurple1 | MediumPurple2 | MediumPurple3 | MediumPurple4 | MediumSeaGreen | MediumSlateBlue | MediumSpringGreen | MediumTurquoise | MediumVioletRed | MidnightBlue | MintCream | MistyRose | MistyRose1 | MistyRose2 | MistyRose3 | MistyRose4 | Moccasin | NavajoWhite | NavajoWhite1 | NavajoWhite2 | NavajoWhite3 | NavajoWhite4 | Navy | NavyBlue | OldLace | OliveDrab | OliveDrab1 | OliveDrab2 | OliveDrab3 | OliveDrab4 | Orange | Orange1 | Orange2 | Orange3 | Orange4 | OrangeRed | OrangeRed1 | OrangeRed2 | OrangeRed3 | OrangeRed4 | Orchid | Orchid1 | Orchid2 | Orchid3 | Orchid4 | PaleGoldenrod | PaleGreen | PaleGreen1 | PaleGreen2 | PaleGreen3 | PaleGreen4 | PaleTurquoise | PaleTurquoise1 | PaleTurquoise2 | PaleTurquoise3 | PaleTurquoise4 | PaleVioletRed | PaleVioletRed1 | PaleVioletRed2 | PaleVioletRed3 | PaleVioletRed4 | PapayaWhip | PeachPuff | PeachPuff1 | PeachPuff2 | PeachPuff3 | PeachPuff4 | Peru | Pink | Pink1 | Pink2 | Pink3 | Pink4 | Plum | Plum1 | Plum2 | Plum3 | Plum4 | PowderBlue | Purple | Purple1 | Purple2 | Purple3 | Purple4 | Red | Red1 | Red2 | Red3 | Red4 | RosyBrown | RosyBrown1 | RosyBrown2 | RosyBrown3 | RosyBrown4 | RoyalBlue | RoyalBlue1 | RoyalBlue2 | RoyalBlue3 | RoyalBlue4 | SaddleBrown | Salmon | Salmon1 | Salmon2 | Salmon3 | Salmon4 | SandyBrown | SeaGreen | SeaGreen1 | SeaGreen2 | SeaGreen3 | SeaGreen4 | SeaShell | SeaShell1 | SeaShell2 | SeaShell3 | SeaShell4 | Sienna | Sienna1 | Sienna2 | Sienna3 | Sienna4 | SkyBlue | SkyBlue1 | SkyBlue2 | SkyBlue3 | SkyBlue4 | SlateBlue | SlateBlue1 | SlateBlue2 | SlateBlue3 | SlateBlue4 | SlateGray | SlateGray1 | SlateGray2 | SlateGray3 | SlateGray4 | Snow | Snow1 | Snow2 | Snow3 | Snow4 | SpringGreen | SpringGreen1 | SpringGreen2 | SpringGreen3 | SpringGreen4 | SteelBlue | SteelBlue1 | SteelBlue2 | SteelBlue3 | SteelBlue4 | Tan | Tan1 | Tan2 | Tan3 | Tan4 | Thistle | Thistle1 | Thistle2 | Thistle3 | Thistle4 | Tomato | Tomato1 | Tomato2 | Tomato3 | Tomato4 | Transparent -- ^ Equivalent to setting @Style [SItem Invisible []]@. | Turquoise | Turquoise1 | Turquoise2 | Turquoise3 | Turquoise4 | Violet | VioletRed | VioletRed1 | VioletRed2 | VioletRed3 | VioletRed4 | Wheat | Wheat1 | Wheat2 | Wheat3 | Wheat4 | White | WhiteSmoke | Yellow | Yellow1 | Yellow2 | Yellow3 | Yellow4 | YellowGreen deriving (Eq, Ord, Bounded, Enum, Show, Read) instance PrintDot X11Color where unqtDot AliceBlue = unqtText "aliceblue" unqtDot AntiqueWhite = unqtText "antiquewhite" unqtDot AntiqueWhite1 = unqtText "antiquewhite1" unqtDot AntiqueWhite2 = unqtText "antiquewhite2" unqtDot AntiqueWhite3 = unqtText "antiquewhite3" unqtDot AntiqueWhite4 = unqtText "antiquewhite4" unqtDot Aquamarine = unqtText "aquamarine" unqtDot Aquamarine1 = unqtText "aquamarine1" unqtDot Aquamarine2 = unqtText "aquamarine2" unqtDot Aquamarine3 = unqtText "aquamarine3" unqtDot Aquamarine4 = unqtText "aquamarine4" unqtDot Azure = unqtText "azure" unqtDot Azure1 = unqtText "azure1" unqtDot Azure2 = unqtText "azure2" unqtDot Azure3 = unqtText "azure3" unqtDot Azure4 = unqtText "azure4" unqtDot Beige = unqtText "beige" unqtDot Bisque = unqtText "bisque" unqtDot Bisque1 = unqtText "bisque1" unqtDot Bisque2 = unqtText "bisque2" unqtDot Bisque3 = unqtText "bisque3" unqtDot Bisque4 = unqtText "bisque4" unqtDot Black = unqtText "black" unqtDot BlanchedAlmond = unqtText "blanchedalmond" unqtDot Blue = unqtText "blue" unqtDot Blue1 = unqtText "blue1" unqtDot Blue2 = unqtText "blue2" unqtDot Blue3 = unqtText "blue3" unqtDot Blue4 = unqtText "blue4" unqtDot BlueViolet = unqtText "blueviolet" unqtDot Brown = unqtText "brown" unqtDot Brown1 = unqtText "brown1" unqtDot Brown2 = unqtText "brown2" unqtDot Brown3 = unqtText "brown3" unqtDot Brown4 = unqtText "brown4" unqtDot Burlywood = unqtText "burlywood" unqtDot Burlywood1 = unqtText "burlywood1" unqtDot Burlywood2 = unqtText "burlywood2" unqtDot Burlywood3 = unqtText "burlywood3" unqtDot Burlywood4 = unqtText "burlywood4" unqtDot CadetBlue = unqtText "cadetblue" unqtDot CadetBlue1 = unqtText "cadetblue1" unqtDot CadetBlue2 = unqtText "cadetblue2" unqtDot CadetBlue3 = unqtText "cadetblue3" unqtDot CadetBlue4 = unqtText "cadetblue4" unqtDot Chartreuse = unqtText "chartreuse" unqtDot Chartreuse1 = unqtText "chartreuse1" unqtDot Chartreuse2 = unqtText "chartreuse2" unqtDot Chartreuse3 = unqtText "chartreuse3" unqtDot Chartreuse4 = unqtText "chartreuse4" unqtDot Chocolate = unqtText "chocolate" unqtDot Chocolate1 = unqtText "chocolate1" unqtDot Chocolate2 = unqtText "chocolate2" unqtDot Chocolate3 = unqtText "chocolate3" unqtDot Chocolate4 = unqtText "chocolate4" unqtDot Coral = unqtText "coral" unqtDot Coral1 = unqtText "coral1" unqtDot Coral2 = unqtText "coral2" unqtDot Coral3 = unqtText "coral3" unqtDot Coral4 = unqtText "coral4" unqtDot CornFlowerBlue = unqtText "cornflowerblue" unqtDot CornSilk = unqtText "cornsilk" unqtDot CornSilk1 = unqtText "cornsilk1" unqtDot CornSilk2 = unqtText "cornsilk2" unqtDot CornSilk3 = unqtText "cornsilk3" unqtDot CornSilk4 = unqtText "cornsilk4" unqtDot Crimson = unqtText "crimson" unqtDot Cyan = unqtText "cyan" unqtDot Cyan1 = unqtText "cyan1" unqtDot Cyan2 = unqtText "cyan2" unqtDot Cyan3 = unqtText "cyan3" unqtDot Cyan4 = unqtText "cyan4" unqtDot DarkGoldenrod = unqtText "darkgoldenrod" unqtDot DarkGoldenrod1 = unqtText "darkgoldenrod1" unqtDot DarkGoldenrod2 = unqtText "darkgoldenrod2" unqtDot DarkGoldenrod3 = unqtText "darkgoldenrod3" unqtDot DarkGoldenrod4 = unqtText "darkgoldenrod4" unqtDot DarkGreen = unqtText "darkgreen" unqtDot Darkkhaki = unqtText "darkkhaki" unqtDot DarkOliveGreen = unqtText "darkolivegreen" unqtDot DarkOliveGreen1 = unqtText "darkolivegreen1" unqtDot DarkOliveGreen2 = unqtText "darkolivegreen2" unqtDot DarkOliveGreen3 = unqtText "darkolivegreen3" unqtDot DarkOliveGreen4 = unqtText "darkolivegreen4" unqtDot DarkOrange = unqtText "darkorange" unqtDot DarkOrange1 = unqtText "darkorange1" unqtDot DarkOrange2 = unqtText "darkorange2" unqtDot DarkOrange3 = unqtText "darkorange3" unqtDot DarkOrange4 = unqtText "darkorange4" unqtDot DarkOrchid = unqtText "darkorchid" unqtDot DarkOrchid1 = unqtText "darkorchid1" unqtDot DarkOrchid2 = unqtText "darkorchid2" unqtDot DarkOrchid3 = unqtText "darkorchid3" unqtDot DarkOrchid4 = unqtText "darkorchid4" unqtDot DarkSalmon = unqtText "darksalmon" unqtDot DarkSeaGreen = unqtText "darkseagreen" unqtDot DarkSeaGreen1 = unqtText "darkseagreen1" unqtDot DarkSeaGreen2 = unqtText "darkseagreen2" unqtDot DarkSeaGreen3 = unqtText "darkseagreen3" unqtDot DarkSeaGreen4 = unqtText "darkseagreen4" unqtDot DarkSlateBlue = unqtText "darkslateblue" unqtDot DarkSlateGray = unqtText "darkslategray" unqtDot DarkSlateGray1 = unqtText "darkslategray1" unqtDot DarkSlateGray2 = unqtText "darkslategray2" unqtDot DarkSlateGray3 = unqtText "darkslategray3" unqtDot DarkSlateGray4 = unqtText "darkslategray4" unqtDot DarkTurquoise = unqtText "darkturquoise" unqtDot DarkViolet = unqtText "darkviolet" unqtDot DeepPink = unqtText "deeppink" unqtDot DeepPink1 = unqtText "deeppink1" unqtDot DeepPink2 = unqtText "deeppink2" unqtDot DeepPink3 = unqtText "deeppink3" unqtDot DeepPink4 = unqtText "deeppink4" unqtDot DeepSkyBlue = unqtText "deepskyblue" unqtDot DeepSkyBlue1 = unqtText "deepskyblue1" unqtDot DeepSkyBlue2 = unqtText "deepskyblue2" unqtDot DeepSkyBlue3 = unqtText "deepskyblue3" unqtDot DeepSkyBlue4 = unqtText "deepskyblue4" unqtDot DimGray = unqtText "dimgray" unqtDot DodgerBlue = unqtText "dodgerblue" unqtDot DodgerBlue1 = unqtText "dodgerblue1" unqtDot DodgerBlue2 = unqtText "dodgerblue2" unqtDot DodgerBlue3 = unqtText "dodgerblue3" unqtDot DodgerBlue4 = unqtText "dodgerblue4" unqtDot Firebrick = unqtText "firebrick" unqtDot Firebrick1 = unqtText "firebrick1" unqtDot Firebrick2 = unqtText "firebrick2" unqtDot Firebrick3 = unqtText "firebrick3" unqtDot Firebrick4 = unqtText "firebrick4" unqtDot FloralWhite = unqtText "floralwhite" unqtDot ForestGreen = unqtText "forestgreen" unqtDot Gainsboro = unqtText "gainsboro" unqtDot GhostWhite = unqtText "ghostwhite" unqtDot Gold = unqtText "gold" unqtDot Gold1 = unqtText "gold1" unqtDot Gold2 = unqtText "gold2" unqtDot Gold3 = unqtText "gold3" unqtDot Gold4 = unqtText "gold4" unqtDot Goldenrod = unqtText "goldenrod" unqtDot Goldenrod1 = unqtText "goldenrod1" unqtDot Goldenrod2 = unqtText "goldenrod2" unqtDot Goldenrod3 = unqtText "goldenrod3" unqtDot Goldenrod4 = unqtText "goldenrod4" unqtDot Gray = unqtText "gray" unqtDot Gray0 = unqtText "gray0" unqtDot Gray1 = unqtText "gray1" unqtDot Gray2 = unqtText "gray2" unqtDot Gray3 = unqtText "gray3" unqtDot Gray4 = unqtText "gray4" unqtDot Gray5 = unqtText "gray5" unqtDot Gray6 = unqtText "gray6" unqtDot Gray7 = unqtText "gray7" unqtDot Gray8 = unqtText "gray8" unqtDot Gray9 = unqtText "gray9" unqtDot Gray10 = unqtText "gray10" unqtDot Gray11 = unqtText "gray11" unqtDot Gray12 = unqtText "gray12" unqtDot Gray13 = unqtText "gray13" unqtDot Gray14 = unqtText "gray14" unqtDot Gray15 = unqtText "gray15" unqtDot Gray16 = unqtText "gray16" unqtDot Gray17 = unqtText "gray17" unqtDot Gray18 = unqtText "gray18" unqtDot Gray19 = unqtText "gray19" unqtDot Gray20 = unqtText "gray20" unqtDot Gray21 = unqtText "gray21" unqtDot Gray22 = unqtText "gray22" unqtDot Gray23 = unqtText "gray23" unqtDot Gray24 = unqtText "gray24" unqtDot Gray25 = unqtText "gray25" unqtDot Gray26 = unqtText "gray26" unqtDot Gray27 = unqtText "gray27" unqtDot Gray28 = unqtText "gray28" unqtDot Gray29 = unqtText "gray29" unqtDot Gray30 = unqtText "gray30" unqtDot Gray31 = unqtText "gray31" unqtDot Gray32 = unqtText "gray32" unqtDot Gray33 = unqtText "gray33" unqtDot Gray34 = unqtText "gray34" unqtDot Gray35 = unqtText "gray35" unqtDot Gray36 = unqtText "gray36" unqtDot Gray37 = unqtText "gray37" unqtDot Gray38 = unqtText "gray38" unqtDot Gray39 = unqtText "gray39" unqtDot Gray40 = unqtText "gray40" unqtDot Gray41 = unqtText "gray41" unqtDot Gray42 = unqtText "gray42" unqtDot Gray43 = unqtText "gray43" unqtDot Gray44 = unqtText "gray44" unqtDot Gray45 = unqtText "gray45" unqtDot Gray46 = unqtText "gray46" unqtDot Gray47 = unqtText "gray47" unqtDot Gray48 = unqtText "gray48" unqtDot Gray49 = unqtText "gray49" unqtDot Gray50 = unqtText "gray50" unqtDot Gray51 = unqtText "gray51" unqtDot Gray52 = unqtText "gray52" unqtDot Gray53 = unqtText "gray53" unqtDot Gray54 = unqtText "gray54" unqtDot Gray55 = unqtText "gray55" unqtDot Gray56 = unqtText "gray56" unqtDot Gray57 = unqtText "gray57" unqtDot Gray58 = unqtText "gray58" unqtDot Gray59 = unqtText "gray59" unqtDot Gray60 = unqtText "gray60" unqtDot Gray61 = unqtText "gray61" unqtDot Gray62 = unqtText "gray62" unqtDot Gray63 = unqtText "gray63" unqtDot Gray64 = unqtText "gray64" unqtDot Gray65 = unqtText "gray65" unqtDot Gray66 = unqtText "gray66" unqtDot Gray67 = unqtText "gray67" unqtDot Gray68 = unqtText "gray68" unqtDot Gray69 = unqtText "gray69" unqtDot Gray70 = unqtText "gray70" unqtDot Gray71 = unqtText "gray71" unqtDot Gray72 = unqtText "gray72" unqtDot Gray73 = unqtText "gray73" unqtDot Gray74 = unqtText "gray74" unqtDot Gray75 = unqtText "gray75" unqtDot Gray76 = unqtText "gray76" unqtDot Gray77 = unqtText "gray77" unqtDot Gray78 = unqtText "gray78" unqtDot Gray79 = unqtText "gray79" unqtDot Gray80 = unqtText "gray80" unqtDot Gray81 = unqtText "gray81" unqtDot Gray82 = unqtText "gray82" unqtDot Gray83 = unqtText "gray83" unqtDot Gray84 = unqtText "gray84" unqtDot Gray85 = unqtText "gray85" unqtDot Gray86 = unqtText "gray86" unqtDot Gray87 = unqtText "gray87" unqtDot Gray88 = unqtText "gray88" unqtDot Gray89 = unqtText "gray89" unqtDot Gray90 = unqtText "gray90" unqtDot Gray91 = unqtText "gray91" unqtDot Gray92 = unqtText "gray92" unqtDot Gray93 = unqtText "gray93" unqtDot Gray94 = unqtText "gray94" unqtDot Gray95 = unqtText "gray95" unqtDot Gray96 = unqtText "gray96" unqtDot Gray97 = unqtText "gray97" unqtDot Gray98 = unqtText "gray98" unqtDot Gray99 = unqtText "gray99" unqtDot Gray100 = unqtText "gray100" unqtDot Green = unqtText "green" unqtDot Green1 = unqtText "green1" unqtDot Green2 = unqtText "green2" unqtDot Green3 = unqtText "green3" unqtDot Green4 = unqtText "green4" unqtDot GreenYellow = unqtText "greenyellow" unqtDot HoneyDew = unqtText "honeydew" unqtDot HoneyDew1 = unqtText "honeydew1" unqtDot HoneyDew2 = unqtText "honeydew2" unqtDot HoneyDew3 = unqtText "honeydew3" unqtDot HoneyDew4 = unqtText "honeydew4" unqtDot HotPink = unqtText "hotpink" unqtDot HotPink1 = unqtText "hotpink1" unqtDot HotPink2 = unqtText "hotpink2" unqtDot HotPink3 = unqtText "hotpink3" unqtDot HotPink4 = unqtText "hotpink4" unqtDot IndianRed = unqtText "indianred" unqtDot IndianRed1 = unqtText "indianred1" unqtDot IndianRed2 = unqtText "indianred2" unqtDot IndianRed3 = unqtText "indianred3" unqtDot IndianRed4 = unqtText "indianred4" unqtDot Indigo = unqtText "indigo" unqtDot Ivory = unqtText "ivory" unqtDot Ivory1 = unqtText "ivory1" unqtDot Ivory2 = unqtText "ivory2" unqtDot Ivory3 = unqtText "ivory3" unqtDot Ivory4 = unqtText "ivory4" unqtDot Khaki = unqtText "khaki" unqtDot Khaki1 = unqtText "khaki1" unqtDot Khaki2 = unqtText "khaki2" unqtDot Khaki3 = unqtText "khaki3" unqtDot Khaki4 = unqtText "khaki4" unqtDot Lavender = unqtText "lavender" unqtDot LavenderBlush = unqtText "lavenderblush" unqtDot LavenderBlush1 = unqtText "lavenderblush1" unqtDot LavenderBlush2 = unqtText "lavenderblush2" unqtDot LavenderBlush3 = unqtText "lavenderblush3" unqtDot LavenderBlush4 = unqtText "lavenderblush4" unqtDot LawnGreen = unqtText "lawngreen" unqtDot LemonChiffon = unqtText "lemonchiffon" unqtDot LemonChiffon1 = unqtText "lemonchiffon1" unqtDot LemonChiffon2 = unqtText "lemonchiffon2" unqtDot LemonChiffon3 = unqtText "lemonchiffon3" unqtDot LemonChiffon4 = unqtText "lemonchiffon4" unqtDot LightBlue = unqtText "lightblue" unqtDot LightBlue1 = unqtText "lightblue1" unqtDot LightBlue2 = unqtText "lightblue2" unqtDot LightBlue3 = unqtText "lightblue3" unqtDot LightBlue4 = unqtText "lightblue4" unqtDot LightCoral = unqtText "lightcoral" unqtDot LightCyan = unqtText "lightcyan" unqtDot LightCyan1 = unqtText "lightcyan1" unqtDot LightCyan2 = unqtText "lightcyan2" unqtDot LightCyan3 = unqtText "lightcyan3" unqtDot LightCyan4 = unqtText "lightcyan4" unqtDot LightGoldenrod = unqtText "lightgoldenrod" unqtDot LightGoldenrod1 = unqtText "lightgoldenrod1" unqtDot LightGoldenrod2 = unqtText "lightgoldenrod2" unqtDot LightGoldenrod3 = unqtText "lightgoldenrod3" unqtDot LightGoldenrod4 = unqtText "lightgoldenrod4" unqtDot LightGoldenrodYellow = unqtText "lightgoldenrodyellow" unqtDot LightGray = unqtText "lightgray" unqtDot LightPink = unqtText "lightpink" unqtDot LightPink1 = unqtText "lightpink1" unqtDot LightPink2 = unqtText "lightpink2" unqtDot LightPink3 = unqtText "lightpink3" unqtDot LightPink4 = unqtText "lightpink4" unqtDot LightSalmon = unqtText "lightsalmon" unqtDot LightSalmon1 = unqtText "lightsalmon1" unqtDot LightSalmon2 = unqtText "lightsalmon2" unqtDot LightSalmon3 = unqtText "lightsalmon3" unqtDot LightSalmon4 = unqtText "lightsalmon4" unqtDot LightSeaGreen = unqtText "lightseagreen" unqtDot LightSkyBlue = unqtText "lightskyblue" unqtDot LightSkyBlue1 = unqtText "lightskyblue1" unqtDot LightSkyBlue2 = unqtText "lightskyblue2" unqtDot LightSkyBlue3 = unqtText "lightskyblue3" unqtDot LightSkyBlue4 = unqtText "lightskyblue4" unqtDot LightSlateBlue = unqtText "lightslateblue" unqtDot LightSlateGray = unqtText "lightslategray" unqtDot LightSteelBlue = unqtText "lightsteelblue" unqtDot LightSteelBlue1 = unqtText "lightsteelblue1" unqtDot LightSteelBlue2 = unqtText "lightsteelblue2" unqtDot LightSteelBlue3 = unqtText "lightsteelblue3" unqtDot LightSteelBlue4 = unqtText "lightsteelblue4" unqtDot LightYellow = unqtText "lightyellow" unqtDot LightYellow1 = unqtText "lightyellow1" unqtDot LightYellow2 = unqtText "lightyellow2" unqtDot LightYellow3 = unqtText "lightyellow3" unqtDot LightYellow4 = unqtText "lightyellow4" unqtDot LimeGreen = unqtText "limegreen" unqtDot Linen = unqtText "linen" unqtDot Magenta = unqtText "magenta" unqtDot Magenta1 = unqtText "magenta1" unqtDot Magenta2 = unqtText "magenta2" unqtDot Magenta3 = unqtText "magenta3" unqtDot Magenta4 = unqtText "magenta4" unqtDot Maroon = unqtText "maroon" unqtDot Maroon1 = unqtText "maroon1" unqtDot Maroon2 = unqtText "maroon2" unqtDot Maroon3 = unqtText "maroon3" unqtDot Maroon4 = unqtText "maroon4" unqtDot MediumAquamarine = unqtText "mediumaquamarine" unqtDot MediumBlue = unqtText "mediumblue" unqtDot MediumOrchid = unqtText "mediumorchid" unqtDot MediumOrchid1 = unqtText "mediumorchid1" unqtDot MediumOrchid2 = unqtText "mediumorchid2" unqtDot MediumOrchid3 = unqtText "mediumorchid3" unqtDot MediumOrchid4 = unqtText "mediumorchid4" unqtDot MediumPurple = unqtText "mediumpurple" unqtDot MediumPurple1 = unqtText "mediumpurple1" unqtDot MediumPurple2 = unqtText "mediumpurple2" unqtDot MediumPurple3 = unqtText "mediumpurple3" unqtDot MediumPurple4 = unqtText "mediumpurple4" unqtDot MediumSeaGreen = unqtText "mediumseagreen" unqtDot MediumSlateBlue = unqtText "mediumslateblue" unqtDot MediumSpringGreen = unqtText "mediumspringgreen" unqtDot MediumTurquoise = unqtText "mediumturquoise" unqtDot MediumVioletRed = unqtText "mediumvioletred" unqtDot MidnightBlue = unqtText "midnightblue" unqtDot MintCream = unqtText "mintcream" unqtDot MistyRose = unqtText "mistyrose" unqtDot MistyRose1 = unqtText "mistyrose1" unqtDot MistyRose2 = unqtText "mistyrose2" unqtDot MistyRose3 = unqtText "mistyrose3" unqtDot MistyRose4 = unqtText "mistyrose4" unqtDot Moccasin = unqtText "moccasin" unqtDot NavajoWhite = unqtText "navajowhite" unqtDot NavajoWhite1 = unqtText "navajowhite1" unqtDot NavajoWhite2 = unqtText "navajowhite2" unqtDot NavajoWhite3 = unqtText "navajowhite3" unqtDot NavajoWhite4 = unqtText "navajowhite4" unqtDot Navy = unqtText "navy" unqtDot NavyBlue = unqtText "navyblue" unqtDot OldLace = unqtText "oldlace" unqtDot OliveDrab = unqtText "olivedrab" unqtDot OliveDrab1 = unqtText "olivedrab1" unqtDot OliveDrab2 = unqtText "olivedrab2" unqtDot OliveDrab3 = unqtText "olivedrab3" unqtDot OliveDrab4 = unqtText "olivedrab4" unqtDot Orange = unqtText "orange" unqtDot Orange1 = unqtText "orange1" unqtDot Orange2 = unqtText "orange2" unqtDot Orange3 = unqtText "orange3" unqtDot Orange4 = unqtText "orange4" unqtDot OrangeRed = unqtText "orangered" unqtDot OrangeRed1 = unqtText "orangered1" unqtDot OrangeRed2 = unqtText "orangered2" unqtDot OrangeRed3 = unqtText "orangered3" unqtDot OrangeRed4 = unqtText "orangered4" unqtDot Orchid = unqtText "orchid" unqtDot Orchid1 = unqtText "orchid1" unqtDot Orchid2 = unqtText "orchid2" unqtDot Orchid3 = unqtText "orchid3" unqtDot Orchid4 = unqtText "orchid4" unqtDot PaleGoldenrod = unqtText "palegoldenrod" unqtDot PaleGreen = unqtText "palegreen" unqtDot PaleGreen1 = unqtText "palegreen1" unqtDot PaleGreen2 = unqtText "palegreen2" unqtDot PaleGreen3 = unqtText "palegreen3" unqtDot PaleGreen4 = unqtText "palegreen4" unqtDot PaleTurquoise = unqtText "paleturquoise" unqtDot PaleTurquoise1 = unqtText "paleturquoise1" unqtDot PaleTurquoise2 = unqtText "paleturquoise2" unqtDot PaleTurquoise3 = unqtText "paleturquoise3" unqtDot PaleTurquoise4 = unqtText "paleturquoise4" unqtDot PaleVioletRed = unqtText "palevioletred" unqtDot PaleVioletRed1 = unqtText "palevioletred1" unqtDot PaleVioletRed2 = unqtText "palevioletred2" unqtDot PaleVioletRed3 = unqtText "palevioletred3" unqtDot PaleVioletRed4 = unqtText "palevioletred4" unqtDot PapayaWhip = unqtText "papayawhip" unqtDot PeachPuff = unqtText "peachpuff" unqtDot PeachPuff1 = unqtText "peachpuff1" unqtDot PeachPuff2 = unqtText "peachpuff2" unqtDot PeachPuff3 = unqtText "peachpuff3" unqtDot PeachPuff4 = unqtText "peachpuff4" unqtDot Peru = unqtText "peru" unqtDot Pink = unqtText "pink" unqtDot Pink1 = unqtText "pink1" unqtDot Pink2 = unqtText "pink2" unqtDot Pink3 = unqtText "pink3" unqtDot Pink4 = unqtText "pink4" unqtDot Plum = unqtText "plum" unqtDot Plum1 = unqtText "plum1" unqtDot Plum2 = unqtText "plum2" unqtDot Plum3 = unqtText "plum3" unqtDot Plum4 = unqtText "plum4" unqtDot PowderBlue = unqtText "powderblue" unqtDot Purple = unqtText "purple" unqtDot Purple1 = unqtText "purple1" unqtDot Purple2 = unqtText "purple2" unqtDot Purple3 = unqtText "purple3" unqtDot Purple4 = unqtText "purple4" unqtDot Red = unqtText "red" unqtDot Red1 = unqtText "red1" unqtDot Red2 = unqtText "red2" unqtDot Red3 = unqtText "red3" unqtDot Red4 = unqtText "red4" unqtDot RosyBrown = unqtText "rosybrown" unqtDot RosyBrown1 = unqtText "rosybrown1" unqtDot RosyBrown2 = unqtText "rosybrown2" unqtDot RosyBrown3 = unqtText "rosybrown3" unqtDot RosyBrown4 = unqtText "rosybrown4" unqtDot RoyalBlue = unqtText "royalblue" unqtDot RoyalBlue1 = unqtText "royalblue1" unqtDot RoyalBlue2 = unqtText "royalblue2" unqtDot RoyalBlue3 = unqtText "royalblue3" unqtDot RoyalBlue4 = unqtText "royalblue4" unqtDot SaddleBrown = unqtText "saddlebrown" unqtDot Salmon = unqtText "salmon" unqtDot Salmon1 = unqtText "salmon1" unqtDot Salmon2 = unqtText "salmon2" unqtDot Salmon3 = unqtText "salmon3" unqtDot Salmon4 = unqtText "salmon4" unqtDot SandyBrown = unqtText "sandybrown" unqtDot SeaGreen = unqtText "seagreen" unqtDot SeaGreen1 = unqtText "seagreen1" unqtDot SeaGreen2 = unqtText "seagreen2" unqtDot SeaGreen3 = unqtText "seagreen3" unqtDot SeaGreen4 = unqtText "seagreen4" unqtDot SeaShell = unqtText "seashell" unqtDot SeaShell1 = unqtText "seashell1" unqtDot SeaShell2 = unqtText "seashell2" unqtDot SeaShell3 = unqtText "seashell3" unqtDot SeaShell4 = unqtText "seashell4" unqtDot Sienna = unqtText "sienna" unqtDot Sienna1 = unqtText "sienna1" unqtDot Sienna2 = unqtText "sienna2" unqtDot Sienna3 = unqtText "sienna3" unqtDot Sienna4 = unqtText "sienna4" unqtDot SkyBlue = unqtText "skyblue" unqtDot SkyBlue1 = unqtText "skyblue1" unqtDot SkyBlue2 = unqtText "skyblue2" unqtDot SkyBlue3 = unqtText "skyblue3" unqtDot SkyBlue4 = unqtText "skyblue4" unqtDot SlateBlue = unqtText "slateblue" unqtDot SlateBlue1 = unqtText "slateblue1" unqtDot SlateBlue2 = unqtText "slateblue2" unqtDot SlateBlue3 = unqtText "slateblue3" unqtDot SlateBlue4 = unqtText "slateblue4" unqtDot SlateGray = unqtText "slategray" unqtDot SlateGray1 = unqtText "slategray1" unqtDot SlateGray2 = unqtText "slategray2" unqtDot SlateGray3 = unqtText "slategray3" unqtDot SlateGray4 = unqtText "slategray4" unqtDot Snow = unqtText "snow" unqtDot Snow1 = unqtText "snow1" unqtDot Snow2 = unqtText "snow2" unqtDot Snow3 = unqtText "snow3" unqtDot Snow4 = unqtText "snow4" unqtDot SpringGreen = unqtText "springgreen" unqtDot SpringGreen1 = unqtText "springgreen1" unqtDot SpringGreen2 = unqtText "springgreen2" unqtDot SpringGreen3 = unqtText "springgreen3" unqtDot SpringGreen4 = unqtText "springgreen4" unqtDot SteelBlue = unqtText "steelblue" unqtDot SteelBlue1 = unqtText "steelblue1" unqtDot SteelBlue2 = unqtText "steelblue2" unqtDot SteelBlue3 = unqtText "steelblue3" unqtDot SteelBlue4 = unqtText "steelblue4" unqtDot Tan = unqtText "tan" unqtDot Tan1 = unqtText "tan1" unqtDot Tan2 = unqtText "tan2" unqtDot Tan3 = unqtText "tan3" unqtDot Tan4 = unqtText "tan4" unqtDot Thistle = unqtText "thistle" unqtDot Thistle1 = unqtText "thistle1" unqtDot Thistle2 = unqtText "thistle2" unqtDot Thistle3 = unqtText "thistle3" unqtDot Thistle4 = unqtText "thistle4" unqtDot Tomato = unqtText "tomato" unqtDot Tomato1 = unqtText "tomato1" unqtDot Tomato2 = unqtText "tomato2" unqtDot Tomato3 = unqtText "tomato3" unqtDot Tomato4 = unqtText "tomato4" unqtDot Transparent = unqtText "transparent" unqtDot Turquoise = unqtText "turquoise" unqtDot Turquoise1 = unqtText "turquoise1" unqtDot Turquoise2 = unqtText "turquoise2" unqtDot Turquoise3 = unqtText "turquoise3" unqtDot Turquoise4 = unqtText "turquoise4" unqtDot Violet = unqtText "violet" unqtDot VioletRed = unqtText "violetred" unqtDot VioletRed1 = unqtText "violetred1" unqtDot VioletRed2 = unqtText "violetred2" unqtDot VioletRed3 = unqtText "violetred3" unqtDot VioletRed4 = unqtText "violetred4" unqtDot Wheat = unqtText "wheat" unqtDot Wheat1 = unqtText "wheat1" unqtDot Wheat2 = unqtText "wheat2" unqtDot Wheat3 = unqtText "wheat3" unqtDot Wheat4 = unqtText "wheat4" unqtDot White = unqtText "white" unqtDot WhiteSmoke = unqtText "whitesmoke" unqtDot Yellow = unqtText "yellow" unqtDot Yellow1 = unqtText "yellow1" unqtDot Yellow2 = unqtText "yellow2" unqtDot Yellow3 = unqtText "yellow3" unqtDot Yellow4 = unqtText "yellow4" unqtDot YellowGreen = unqtText "yellowgreen" instance ParseDot X11Color where parseUnqt = stringValue [ ("aliceblue", AliceBlue) , ("antiquewhite", AntiqueWhite) , ("antiquewhite1", AntiqueWhite1) , ("antiquewhite2", AntiqueWhite2) , ("antiquewhite3", AntiqueWhite3) , ("antiquewhite4", AntiqueWhite4) , ("aquamarine", Aquamarine) , ("aquamarine1", Aquamarine1) , ("aquamarine2", Aquamarine2) , ("aquamarine3", Aquamarine3) , ("aquamarine4", Aquamarine4) , ("azure", Azure) , ("azure1", Azure1) , ("azure2", Azure2) , ("azure3", Azure3) , ("azure4", Azure4) , ("beige", Beige) , ("bisque", Bisque) , ("bisque1", Bisque1) , ("bisque2", Bisque2) , ("bisque3", Bisque3) , ("bisque4", Bisque4) , ("black", Black) , ("blanchedalmond", BlanchedAlmond) , ("blue", Blue) , ("blue1", Blue1) , ("blue2", Blue2) , ("blue3", Blue3) , ("blue4", Blue4) , ("blueviolet", BlueViolet) , ("brown", Brown) , ("brown1", Brown1) , ("brown2", Brown2) , ("brown3", Brown3) , ("brown4", Brown4) , ("burlywood", Burlywood) , ("burlywood1", Burlywood1) , ("burlywood2", Burlywood2) , ("burlywood3", Burlywood3) , ("burlywood4", Burlywood4) , ("cadetblue", CadetBlue) , ("cadetblue1", CadetBlue1) , ("cadetblue2", CadetBlue2) , ("cadetblue3", CadetBlue3) , ("cadetblue4", CadetBlue4) , ("chartreuse", Chartreuse) , ("chartreuse1", Chartreuse1) , ("chartreuse2", Chartreuse2) , ("chartreuse3", Chartreuse3) , ("chartreuse4", Chartreuse4) , ("chocolate", Chocolate) , ("chocolate1", Chocolate1) , ("chocolate2", Chocolate2) , ("chocolate3", Chocolate3) , ("chocolate4", Chocolate4) , ("coral", Coral) , ("coral1", Coral1) , ("coral2", Coral2) , ("coral3", Coral3) , ("coral4", Coral4) , ("cornflowerblue", CornFlowerBlue) , ("cornsilk", CornSilk) , ("cornsilk1", CornSilk1) , ("cornsilk2", CornSilk2) , ("cornsilk3", CornSilk3) , ("cornsilk4", CornSilk4) , ("crimson", Crimson) , ("cyan", Cyan) , ("cyan1", Cyan1) , ("cyan2", Cyan2) , ("cyan3", Cyan3) , ("cyan4", Cyan4) , ("darkgoldenrod", DarkGoldenrod) , ("darkgoldenrod1", DarkGoldenrod1) , ("darkgoldenrod2", DarkGoldenrod2) , ("darkgoldenrod3", DarkGoldenrod3) , ("darkgoldenrod4", DarkGoldenrod4) , ("darkgreen", DarkGreen) , ("darkkhaki", Darkkhaki) , ("darkolivegreen", DarkOliveGreen) , ("darkolivegreen1", DarkOliveGreen1) , ("darkolivegreen2", DarkOliveGreen2) , ("darkolivegreen3", DarkOliveGreen3) , ("darkolivegreen4", DarkOliveGreen4) , ("darkorange", DarkOrange) , ("darkorange1", DarkOrange1) , ("darkorange2", DarkOrange2) , ("darkorange3", DarkOrange3) , ("darkorange4", DarkOrange4) , ("darkorchid", DarkOrchid) , ("darkorchid1", DarkOrchid1) , ("darkorchid2", DarkOrchid2) , ("darkorchid3", DarkOrchid3) , ("darkorchid4", DarkOrchid4) , ("darksalmon", DarkSalmon) , ("darkseagreen", DarkSeaGreen) , ("darkseagreen1", DarkSeaGreen1) , ("darkseagreen2", DarkSeaGreen2) , ("darkseagreen3", DarkSeaGreen3) , ("darkseagreen4", DarkSeaGreen4) , ("darkslateblue", DarkSlateBlue) , ("darkslategray", DarkSlateGray) , ("darkslategrey", DarkSlateGray) , ("darkslategray1", DarkSlateGray1) , ("darkslategrey1", DarkSlateGray1) , ("darkslategray2", DarkSlateGray2) , ("darkslategrey2", DarkSlateGray2) , ("darkslategray3", DarkSlateGray3) , ("darkslategrey3", DarkSlateGray3) , ("darkslategray4", DarkSlateGray4) , ("darkslategrey4", DarkSlateGray4) , ("darkturquoise", DarkTurquoise) , ("darkviolet", DarkViolet) , ("deeppink", DeepPink) , ("deeppink1", DeepPink1) , ("deeppink2", DeepPink2) , ("deeppink3", DeepPink3) , ("deeppink4", DeepPink4) , ("deepskyblue", DeepSkyBlue) , ("deepskyblue1", DeepSkyBlue1) , ("deepskyblue2", DeepSkyBlue2) , ("deepskyblue3", DeepSkyBlue3) , ("deepskyblue4", DeepSkyBlue4) , ("dimgray", DimGray) , ("dimgrey", DimGray) , ("dodgerblue", DodgerBlue) , ("dodgerblue1", DodgerBlue1) , ("dodgerblue2", DodgerBlue2) , ("dodgerblue3", DodgerBlue3) , ("dodgerblue4", DodgerBlue4) , ("firebrick", Firebrick) , ("firebrick1", Firebrick1) , ("firebrick2", Firebrick2) , ("firebrick3", Firebrick3) , ("firebrick4", Firebrick4) , ("floralwhite", FloralWhite) , ("forestgreen", ForestGreen) , ("gainsboro", Gainsboro) , ("ghostwhite", GhostWhite) , ("gold", Gold) , ("gold1", Gold1) , ("gold2", Gold2) , ("gold3", Gold3) , ("gold4", Gold4) , ("goldenrod", Goldenrod) , ("goldenrod1", Goldenrod1) , ("goldenrod2", Goldenrod2) , ("goldenrod3", Goldenrod3) , ("goldenrod4", Goldenrod4) , ("gray", Gray) , ("grey", Gray) , ("gray0", Gray0) , ("grey0", Gray0) , ("gray1", Gray1) , ("grey1", Gray1) , ("gray2", Gray2) , ("grey2", Gray2) , ("gray3", Gray3) , ("grey3", Gray3) , ("gray4", Gray4) , ("grey4", Gray4) , ("gray5", Gray5) , ("grey5", Gray5) , ("gray6", Gray6) , ("grey6", Gray6) , ("gray7", Gray7) , ("grey7", Gray7) , ("gray8", Gray8) , ("grey8", Gray8) , ("gray9", Gray9) , ("grey9", Gray9) , ("gray10", Gray10) , ("grey10", Gray10) , ("gray11", Gray11) , ("grey11", Gray11) , ("gray12", Gray12) , ("grey12", Gray12) , ("gray13", Gray13) , ("grey13", Gray13) , ("gray14", Gray14) , ("grey14", Gray14) , ("gray15", Gray15) , ("grey15", Gray15) , ("gray16", Gray16) , ("grey16", Gray16) , ("gray17", Gray17) , ("grey17", Gray17) , ("gray18", Gray18) , ("grey18", Gray18) , ("gray19", Gray19) , ("grey19", Gray19) , ("gray20", Gray20) , ("grey20", Gray20) , ("gray21", Gray21) , ("grey21", Gray21) , ("gray22", Gray22) , ("grey22", Gray22) , ("gray23", Gray23) , ("grey23", Gray23) , ("gray24", Gray24) , ("grey24", Gray24) , ("gray25", Gray25) , ("grey25", Gray25) , ("gray26", Gray26) , ("grey26", Gray26) , ("gray27", Gray27) , ("grey27", Gray27) , ("gray28", Gray28) , ("grey28", Gray28) , ("gray29", Gray29) , ("grey29", Gray29) , ("gray30", Gray30) , ("grey30", Gray30) , ("gray31", Gray31) , ("grey31", Gray31) , ("gray32", Gray32) , ("grey32", Gray32) , ("gray33", Gray33) , ("grey33", Gray33) , ("gray34", Gray34) , ("grey34", Gray34) , ("gray35", Gray35) , ("grey35", Gray35) , ("gray36", Gray36) , ("grey36", Gray36) , ("gray37", Gray37) , ("grey37", Gray37) , ("gray38", Gray38) , ("grey38", Gray38) , ("gray39", Gray39) , ("grey39", Gray39) , ("gray40", Gray40) , ("grey40", Gray40) , ("gray41", Gray41) , ("grey41", Gray41) , ("gray42", Gray42) , ("grey42", Gray42) , ("gray43", Gray43) , ("grey43", Gray43) , ("gray44", Gray44) , ("grey44", Gray44) , ("gray45", Gray45) , ("grey45", Gray45) , ("gray46", Gray46) , ("grey46", Gray46) , ("gray47", Gray47) , ("grey47", Gray47) , ("gray48", Gray48) , ("grey48", Gray48) , ("gray49", Gray49) , ("grey49", Gray49) , ("gray50", Gray50) , ("grey50", Gray50) , ("gray51", Gray51) , ("grey51", Gray51) , ("gray52", Gray52) , ("grey52", Gray52) , ("gray53", Gray53) , ("grey53", Gray53) , ("gray54", Gray54) , ("grey54", Gray54) , ("gray55", Gray55) , ("grey55", Gray55) , ("gray56", Gray56) , ("grey56", Gray56) , ("gray57", Gray57) , ("grey57", Gray57) , ("gray58", Gray58) , ("grey58", Gray58) , ("gray59", Gray59) , ("grey59", Gray59) , ("gray60", Gray60) , ("grey60", Gray60) , ("gray61", Gray61) , ("grey61", Gray61) , ("gray62", Gray62) , ("grey62", Gray62) , ("gray63", Gray63) , ("grey63", Gray63) , ("gray64", Gray64) , ("grey64", Gray64) , ("gray65", Gray65) , ("grey65", Gray65) , ("gray66", Gray66) , ("grey66", Gray66) , ("gray67", Gray67) , ("grey67", Gray67) , ("gray68", Gray68) , ("grey68", Gray68) , ("gray69", Gray69) , ("grey69", Gray69) , ("gray70", Gray70) , ("grey70", Gray70) , ("gray71", Gray71) , ("grey71", Gray71) , ("gray72", Gray72) , ("grey72", Gray72) , ("gray73", Gray73) , ("grey73", Gray73) , ("gray74", Gray74) , ("grey74", Gray74) , ("gray75", Gray75) , ("grey75", Gray75) , ("gray76", Gray76) , ("grey76", Gray76) , ("gray77", Gray77) , ("grey77", Gray77) , ("gray78", Gray78) , ("grey78", Gray78) , ("gray79", Gray79) , ("grey79", Gray79) , ("gray80", Gray80) , ("grey80", Gray80) , ("gray81", Gray81) , ("grey81", Gray81) , ("gray82", Gray82) , ("grey82", Gray82) , ("gray83", Gray83) , ("grey83", Gray83) , ("gray84", Gray84) , ("grey84", Gray84) , ("gray85", Gray85) , ("grey85", Gray85) , ("gray86", Gray86) , ("grey86", Gray86) , ("gray87", Gray87) , ("grey87", Gray87) , ("gray88", Gray88) , ("grey88", Gray88) , ("gray89", Gray89) , ("grey89", Gray89) , ("gray90", Gray90) , ("grey90", Gray90) , ("gray91", Gray91) , ("grey91", Gray91) , ("gray92", Gray92) , ("grey92", Gray92) , ("gray93", Gray93) , ("grey93", Gray93) , ("gray94", Gray94) , ("grey94", Gray94) , ("gray95", Gray95) , ("grey95", Gray95) , ("gray96", Gray96) , ("grey96", Gray96) , ("gray97", Gray97) , ("grey97", Gray97) , ("gray98", Gray98) , ("grey98", Gray98) , ("gray99", Gray99) , ("grey99", Gray99) , ("gray100", Gray100) , ("grey100", Gray100) , ("green", Green) , ("green1", Green1) , ("green2", Green2) , ("green3", Green3) , ("green4", Green4) , ("greenyellow", GreenYellow) , ("honeydew", HoneyDew) , ("honeydew1", HoneyDew1) , ("honeydew2", HoneyDew2) , ("honeydew3", HoneyDew3) , ("honeydew4", HoneyDew4) , ("hotpink", HotPink) , ("hotpink1", HotPink1) , ("hotpink2", HotPink2) , ("hotpink3", HotPink3) , ("hotpink4", HotPink4) , ("indianred", IndianRed) , ("indianred1", IndianRed1) , ("indianred2", IndianRed2) , ("indianred3", IndianRed3) , ("indianred4", IndianRed4) , ("indigo", Indigo) , ("ivory", Ivory) , ("ivory1", Ivory1) , ("ivory2", Ivory2) , ("ivory3", Ivory3) , ("ivory4", Ivory4) , ("khaki", Khaki) , ("khaki1", Khaki1) , ("khaki2", Khaki2) , ("khaki3", Khaki3) , ("khaki4", Khaki4) , ("lavender", Lavender) , ("lavenderblush", LavenderBlush) , ("lavenderblush1", LavenderBlush1) , ("lavenderblush2", LavenderBlush2) , ("lavenderblush3", LavenderBlush3) , ("lavenderblush4", LavenderBlush4) , ("lawngreen", LawnGreen) , ("lemonchiffon", LemonChiffon) , ("lemonchiffon1", LemonChiffon1) , ("lemonchiffon2", LemonChiffon2) , ("lemonchiffon3", LemonChiffon3) , ("lemonchiffon4", LemonChiffon4) , ("lightblue", LightBlue) , ("lightblue1", LightBlue1) , ("lightblue2", LightBlue2) , ("lightblue3", LightBlue3) , ("lightblue4", LightBlue4) , ("lightcoral", LightCoral) , ("lightcyan", LightCyan) , ("lightcyan1", LightCyan1) , ("lightcyan2", LightCyan2) , ("lightcyan3", LightCyan3) , ("lightcyan4", LightCyan4) , ("lightgoldenrod", LightGoldenrod) , ("lightgoldenrod1", LightGoldenrod1) , ("lightgoldenrod2", LightGoldenrod2) , ("lightgoldenrod3", LightGoldenrod3) , ("lightgoldenrod4", LightGoldenrod4) , ("lightgoldenrodyellow", LightGoldenrodYellow) , ("lightgray", LightGray) , ("lightgrey", LightGray) , ("lightpink", LightPink) , ("lightpink1", LightPink1) , ("lightpink2", LightPink2) , ("lightpink3", LightPink3) , ("lightpink4", LightPink4) , ("lightsalmon", LightSalmon) , ("lightsalmon1", LightSalmon1) , ("lightsalmon2", LightSalmon2) , ("lightsalmon3", LightSalmon3) , ("lightsalmon4", LightSalmon4) , ("lightseagreen", LightSeaGreen) , ("lightskyblue", LightSkyBlue) , ("lightskyblue1", LightSkyBlue1) , ("lightskyblue2", LightSkyBlue2) , ("lightskyblue3", LightSkyBlue3) , ("lightskyblue4", LightSkyBlue4) , ("lightslateblue", LightSlateBlue) , ("lightslategray", LightSlateGray) , ("lightslategrey", LightSlateGray) , ("lightsteelblue", LightSteelBlue) , ("lightsteelblue1", LightSteelBlue1) , ("lightsteelblue2", LightSteelBlue2) , ("lightsteelblue3", LightSteelBlue3) , ("lightsteelblue4", LightSteelBlue4) , ("lightyellow", LightYellow) , ("lightyellow1", LightYellow1) , ("lightyellow2", LightYellow2) , ("lightyellow3", LightYellow3) , ("lightyellow4", LightYellow4) , ("limegreen", LimeGreen) , ("linen", Linen) , ("magenta", Magenta) , ("magenta1", Magenta1) , ("magenta2", Magenta2) , ("magenta3", Magenta3) , ("magenta4", Magenta4) , ("maroon", Maroon) , ("maroon1", Maroon1) , ("maroon2", Maroon2) , ("maroon3", Maroon3) , ("maroon4", Maroon4) , ("mediumaquamarine", MediumAquamarine) , ("mediumblue", MediumBlue) , ("mediumorchid", MediumOrchid) , ("mediumorchid1", MediumOrchid1) , ("mediumorchid2", MediumOrchid2) , ("mediumorchid3", MediumOrchid3) , ("mediumorchid4", MediumOrchid4) , ("mediumpurple", MediumPurple) , ("mediumpurple1", MediumPurple1) , ("mediumpurple2", MediumPurple2) , ("mediumpurple3", MediumPurple3) , ("mediumpurple4", MediumPurple4) , ("mediumseagreen", MediumSeaGreen) , ("mediumslateblue", MediumSlateBlue) , ("mediumspringgreen", MediumSpringGreen) , ("mediumturquoise", MediumTurquoise) , ("mediumvioletred", MediumVioletRed) , ("midnightblue", MidnightBlue) , ("mintcream", MintCream) , ("mistyrose", MistyRose) , ("mistyrose1", MistyRose1) , ("mistyrose2", MistyRose2) , ("mistyrose3", MistyRose3) , ("mistyrose4", MistyRose4) , ("moccasin", Moccasin) , ("navajowhite", NavajoWhite) , ("navajowhite1", NavajoWhite1) , ("navajowhite2", NavajoWhite2) , ("navajowhite3", NavajoWhite3) , ("navajowhite4", NavajoWhite4) , ("navy", Navy) , ("navyblue", NavyBlue) , ("oldlace", OldLace) , ("olivedrab", OliveDrab) , ("olivedrab1", OliveDrab1) , ("olivedrab2", OliveDrab2) , ("olivedrab3", OliveDrab3) , ("olivedrab4", OliveDrab4) , ("orange", Orange) , ("orange1", Orange1) , ("orange2", Orange2) , ("orange3", Orange3) , ("orange4", Orange4) , ("orangered", OrangeRed) , ("orangered1", OrangeRed1) , ("orangered2", OrangeRed2) , ("orangered3", OrangeRed3) , ("orangered4", OrangeRed4) , ("orchid", Orchid) , ("orchid1", Orchid1) , ("orchid2", Orchid2) , ("orchid3", Orchid3) , ("orchid4", Orchid4) , ("palegoldenrod", PaleGoldenrod) , ("palegreen", PaleGreen) , ("palegreen1", PaleGreen1) , ("palegreen2", PaleGreen2) , ("palegreen3", PaleGreen3) , ("palegreen4", PaleGreen4) , ("paleturquoise", PaleTurquoise) , ("paleturquoise1", PaleTurquoise1) , ("paleturquoise2", PaleTurquoise2) , ("paleturquoise3", PaleTurquoise3) , ("paleturquoise4", PaleTurquoise4) , ("palevioletred", PaleVioletRed) , ("palevioletred1", PaleVioletRed1) , ("palevioletred2", PaleVioletRed2) , ("palevioletred3", PaleVioletRed3) , ("palevioletred4", PaleVioletRed4) , ("papayawhip", PapayaWhip) , ("peachpuff", PeachPuff) , ("peachpuff1", PeachPuff1) , ("peachpuff2", PeachPuff2) , ("peachpuff3", PeachPuff3) , ("peachpuff4", PeachPuff4) , ("peru", Peru) , ("pink", Pink) , ("pink1", Pink1) , ("pink2", Pink2) , ("pink3", Pink3) , ("pink4", Pink4) , ("plum", Plum) , ("plum1", Plum1) , ("plum2", Plum2) , ("plum3", Plum3) , ("plum4", Plum4) , ("powderblue", PowderBlue) , ("purple", Purple) , ("purple1", Purple1) , ("purple2", Purple2) , ("purple3", Purple3) , ("purple4", Purple4) , ("red", Red) , ("red1", Red1) , ("red2", Red2) , ("red3", Red3) , ("red4", Red4) , ("rosybrown", RosyBrown) , ("rosybrown1", RosyBrown1) , ("rosybrown2", RosyBrown2) , ("rosybrown3", RosyBrown3) , ("rosybrown4", RosyBrown4) , ("royalblue", RoyalBlue) , ("royalblue1", RoyalBlue1) , ("royalblue2", RoyalBlue2) , ("royalblue3", RoyalBlue3) , ("royalblue4", RoyalBlue4) , ("saddlebrown", SaddleBrown) , ("salmon", Salmon) , ("salmon1", Salmon1) , ("salmon2", Salmon2) , ("salmon3", Salmon3) , ("salmon4", Salmon4) , ("sandybrown", SandyBrown) , ("seagreen", SeaGreen) , ("seagreen1", SeaGreen1) , ("seagreen2", SeaGreen2) , ("seagreen3", SeaGreen3) , ("seagreen4", SeaGreen4) , ("seashell", SeaShell) , ("seashell1", SeaShell1) , ("seashell2", SeaShell2) , ("seashell3", SeaShell3) , ("seashell4", SeaShell4) , ("sienna", Sienna) , ("sienna1", Sienna1) , ("sienna2", Sienna2) , ("sienna3", Sienna3) , ("sienna4", Sienna4) , ("skyblue", SkyBlue) , ("skyblue1", SkyBlue1) , ("skyblue2", SkyBlue2) , ("skyblue3", SkyBlue3) , ("skyblue4", SkyBlue4) , ("slateblue", SlateBlue) , ("slateblue1", SlateBlue1) , ("slateblue2", SlateBlue2) , ("slateblue3", SlateBlue3) , ("slateblue4", SlateBlue4) , ("slategray", SlateGray) , ("slategrey", SlateGray) , ("slategray1", SlateGray1) , ("slategrey1", SlateGray1) , ("slategray2", SlateGray2) , ("slategrey2", SlateGray2) , ("slategray3", SlateGray3) , ("slategrey3", SlateGray3) , ("slategray4", SlateGray4) , ("slategrey4", SlateGray4) , ("snow", Snow) , ("snow1", Snow1) , ("snow2", Snow2) , ("snow3", Snow3) , ("snow4", Snow4) , ("springgreen", SpringGreen) , ("springgreen1", SpringGreen1) , ("springgreen2", SpringGreen2) , ("springgreen3", SpringGreen3) , ("springgreen4", SpringGreen4) , ("steelblue", SteelBlue) , ("steelblue1", SteelBlue1) , ("steelblue2", SteelBlue2) , ("steelblue3", SteelBlue3) , ("steelblue4", SteelBlue4) , ("tan", Tan) , ("tan1", Tan1) , ("tan2", Tan2) , ("tan3", Tan3) , ("tan4", Tan4) , ("thistle", Thistle) , ("thistle1", Thistle1) , ("thistle2", Thistle2) , ("thistle3", Thistle3) , ("thistle4", Thistle4) , ("tomato", Tomato) , ("tomato1", Tomato1) , ("tomato2", Tomato2) , ("tomato3", Tomato3) , ("tomato4", Tomato4) , ("transparent", Transparent) , ("invis", Transparent) , ("none", Transparent) , ("turquoise", Turquoise) , ("turquoise1", Turquoise1) , ("turquoise2", Turquoise2) , ("turquoise3", Turquoise3) , ("turquoise4", Turquoise4) , ("violet", Violet) , ("violetred", VioletRed) , ("violetred1", VioletRed1) , ("violetred2", VioletRed2) , ("violetred3", VioletRed3) , ("violetred4", VioletRed4) , ("wheat", Wheat) , ("wheat1", Wheat1) , ("wheat2", Wheat2) , ("wheat3", Wheat3) , ("wheat4", Wheat4) , ("white", White) , ("whitesmoke", WhiteSmoke) , ("yellow", Yellow) , ("yellow1", Yellow1) , ("yellow2", Yellow2) , ("yellow3", Yellow3) , ("yellow4", Yellow4) , ("yellowgreen", YellowGreen) ] -- | Convert an 'X11Color' to its equivalent 'Colour' value. Note -- that it uses 'AlphaColour' because of 'Transparent'; all other -- 'X11Color' values are completely opaque. x11Colour :: X11Color -> AlphaColour Double x11Colour AliceBlue = opaque $ sRGB24 240 248 255 x11Colour AntiqueWhite = opaque $ sRGB24 250 235 215 x11Colour AntiqueWhite1 = opaque $ sRGB24 255 239 219 x11Colour AntiqueWhite2 = opaque $ sRGB24 238 223 204 x11Colour AntiqueWhite3 = opaque $ sRGB24 205 192 176 x11Colour AntiqueWhite4 = opaque $ sRGB24 139 131 120 x11Colour Aquamarine = opaque $ sRGB24 127 255 212 x11Colour Aquamarine1 = opaque $ sRGB24 127 255 212 x11Colour Aquamarine2 = opaque $ sRGB24 118 238 198 x11Colour Aquamarine3 = opaque $ sRGB24 102 205 170 x11Colour Aquamarine4 = opaque $ sRGB24 69 139 116 x11Colour Azure = opaque $ sRGB24 240 255 255 x11Colour Azure1 = opaque $ sRGB24 240 255 255 x11Colour Azure2 = opaque $ sRGB24 224 238 238 x11Colour Azure3 = opaque $ sRGB24 193 205 205 x11Colour Azure4 = opaque $ sRGB24 131 139 139 x11Colour Beige = opaque $ sRGB24 245 245 220 x11Colour Bisque = opaque $ sRGB24 255 228 196 x11Colour Bisque1 = opaque $ sRGB24 255 228 196 x11Colour Bisque2 = opaque $ sRGB24 238 213 183 x11Colour Bisque3 = opaque $ sRGB24 205 183 158 x11Colour Bisque4 = opaque $ sRGB24 139 125 107 x11Colour Black = opaque $ sRGB24 0 0 0 x11Colour BlanchedAlmond = opaque $ sRGB24 255 235 205 x11Colour Blue = opaque $ sRGB24 0 0 255 x11Colour Blue1 = opaque $ sRGB24 0 0 255 x11Colour Blue2 = opaque $ sRGB24 0 0 238 x11Colour Blue3 = opaque $ sRGB24 0 0 205 x11Colour Blue4 = opaque $ sRGB24 0 0 139 x11Colour BlueViolet = opaque $ sRGB24 138 43 226 x11Colour Brown = opaque $ sRGB24 165 42 42 x11Colour Brown1 = opaque $ sRGB24 255 64 64 x11Colour Brown2 = opaque $ sRGB24 238 59 59 x11Colour Brown3 = opaque $ sRGB24 205 51 51 x11Colour Brown4 = opaque $ sRGB24 139 35 35 x11Colour Burlywood = opaque $ sRGB24 222 184 135 x11Colour Burlywood1 = opaque $ sRGB24 255 211 155 x11Colour Burlywood2 = opaque $ sRGB24 238 197 145 x11Colour Burlywood3 = opaque $ sRGB24 205 170 125 x11Colour Burlywood4 = opaque $ sRGB24 139 115 85 x11Colour CadetBlue = opaque $ sRGB24 95 158 160 x11Colour CadetBlue1 = opaque $ sRGB24 152 245 255 x11Colour CadetBlue2 = opaque $ sRGB24 142 229 238 x11Colour CadetBlue3 = opaque $ sRGB24 122 197 205 x11Colour CadetBlue4 = opaque $ sRGB24 83 134 139 x11Colour Chartreuse = opaque $ sRGB24 127 255 0 x11Colour Chartreuse1 = opaque $ sRGB24 127 255 0 x11Colour Chartreuse2 = opaque $ sRGB24 118 238 0 x11Colour Chartreuse3 = opaque $ sRGB24 102 205 0 x11Colour Chartreuse4 = opaque $ sRGB24 69 139 0 x11Colour Chocolate = opaque $ sRGB24 210 105 30 x11Colour Chocolate1 = opaque $ sRGB24 255 127 36 x11Colour Chocolate2 = opaque $ sRGB24 238 118 33 x11Colour Chocolate3 = opaque $ sRGB24 205 102 29 x11Colour Chocolate4 = opaque $ sRGB24 139 69 19 x11Colour Coral = opaque $ sRGB24 255 127 80 x11Colour Coral1 = opaque $ sRGB24 255 114 86 x11Colour Coral2 = opaque $ sRGB24 238 106 80 x11Colour Coral3 = opaque $ sRGB24 205 91 69 x11Colour Coral4 = opaque $ sRGB24 139 62 47 x11Colour CornFlowerBlue = opaque $ sRGB24 100 149 237 x11Colour CornSilk = opaque $ sRGB24 255 248 220 x11Colour CornSilk1 = opaque $ sRGB24 255 248 220 x11Colour CornSilk2 = opaque $ sRGB24 238 232 205 x11Colour CornSilk3 = opaque $ sRGB24 205 200 177 x11Colour CornSilk4 = opaque $ sRGB24 139 136 120 x11Colour Crimson = opaque $ sRGB24 220 20 60 x11Colour Cyan = opaque $ sRGB24 0 255 255 x11Colour Cyan1 = opaque $ sRGB24 0 255 255 x11Colour Cyan2 = opaque $ sRGB24 0 238 238 x11Colour Cyan3 = opaque $ sRGB24 0 205 205 x11Colour Cyan4 = opaque $ sRGB24 0 139 139 x11Colour DarkGoldenrod = opaque $ sRGB24 184 134 11 x11Colour DarkGoldenrod1 = opaque $ sRGB24 255 185 15 x11Colour DarkGoldenrod2 = opaque $ sRGB24 238 173 14 x11Colour DarkGoldenrod3 = opaque $ sRGB24 205 149 12 x11Colour DarkGoldenrod4 = opaque $ sRGB24 139 101 8 x11Colour DarkGreen = opaque $ sRGB24 0 100 0 x11Colour Darkkhaki = opaque $ sRGB24 189 183 107 x11Colour DarkOliveGreen = opaque $ sRGB24 85 107 47 x11Colour DarkOliveGreen1 = opaque $ sRGB24 202 255 112 x11Colour DarkOliveGreen2 = opaque $ sRGB24 188 238 104 x11Colour DarkOliveGreen3 = opaque $ sRGB24 162 205 90 x11Colour DarkOliveGreen4 = opaque $ sRGB24 110 139 61 x11Colour DarkOrange = opaque $ sRGB24 255 140 0 x11Colour DarkOrange1 = opaque $ sRGB24 255 127 0 x11Colour DarkOrange2 = opaque $ sRGB24 238 118 0 x11Colour DarkOrange3 = opaque $ sRGB24 205 102 0 x11Colour DarkOrange4 = opaque $ sRGB24 139 69 0 x11Colour DarkOrchid = opaque $ sRGB24 153 50 204 x11Colour DarkOrchid1 = opaque $ sRGB24 191 62 255 x11Colour DarkOrchid2 = opaque $ sRGB24 178 58 238 x11Colour DarkOrchid3 = opaque $ sRGB24 154 50 205 x11Colour DarkOrchid4 = opaque $ sRGB24 104 34 139 x11Colour DarkSalmon = opaque $ sRGB24 233 150 122 x11Colour DarkSeaGreen = opaque $ sRGB24 143 188 143 x11Colour DarkSeaGreen1 = opaque $ sRGB24 193 255 193 x11Colour DarkSeaGreen2 = opaque $ sRGB24 180 238 180 x11Colour DarkSeaGreen3 = opaque $ sRGB24 155 205 155 x11Colour DarkSeaGreen4 = opaque $ sRGB24 105 139 105 x11Colour DarkSlateBlue = opaque $ sRGB24 72 61 139 x11Colour DarkSlateGray = opaque $ sRGB24 47 79 79 x11Colour DarkSlateGray1 = opaque $ sRGB24 151 255 255 x11Colour DarkSlateGray2 = opaque $ sRGB24 141 238 238 x11Colour DarkSlateGray3 = opaque $ sRGB24 121 205 205 x11Colour DarkSlateGray4 = opaque $ sRGB24 82 139 139 x11Colour DarkTurquoise = opaque $ sRGB24 0 206 209 x11Colour DarkViolet = opaque $ sRGB24 148 0 211 x11Colour DeepPink = opaque $ sRGB24 255 20 147 x11Colour DeepPink1 = opaque $ sRGB24 255 20 147 x11Colour DeepPink2 = opaque $ sRGB24 238 18 137 x11Colour DeepPink3 = opaque $ sRGB24 205 16 118 x11Colour DeepPink4 = opaque $ sRGB24 139 10 80 x11Colour DeepSkyBlue = opaque $ sRGB24 0 191 255 x11Colour DeepSkyBlue1 = opaque $ sRGB24 0 191 255 x11Colour DeepSkyBlue2 = opaque $ sRGB24 0 178 238 x11Colour DeepSkyBlue3 = opaque $ sRGB24 0 154 205 x11Colour DeepSkyBlue4 = opaque $ sRGB24 0 104 139 x11Colour DimGray = opaque $ sRGB24 105 105 105 x11Colour DodgerBlue = opaque $ sRGB24 30 144 255 x11Colour DodgerBlue1 = opaque $ sRGB24 30 144 255 x11Colour DodgerBlue2 = opaque $ sRGB24 28 134 238 x11Colour DodgerBlue3 = opaque $ sRGB24 24 116 205 x11Colour DodgerBlue4 = opaque $ sRGB24 16 78 139 x11Colour Firebrick = opaque $ sRGB24 178 34 34 x11Colour Firebrick1 = opaque $ sRGB24 255 48 48 x11Colour Firebrick2 = opaque $ sRGB24 238 44 44 x11Colour Firebrick3 = opaque $ sRGB24 205 38 38 x11Colour Firebrick4 = opaque $ sRGB24 139 26 26 x11Colour FloralWhite = opaque $ sRGB24 255 250 240 x11Colour ForestGreen = opaque $ sRGB24 34 139 34 x11Colour Gainsboro = opaque $ sRGB24 220 220 220 x11Colour GhostWhite = opaque $ sRGB24 248 248 255 x11Colour Gold = opaque $ sRGB24 255 215 0 x11Colour Gold1 = opaque $ sRGB24 255 215 0 x11Colour Gold2 = opaque $ sRGB24 238 201 0 x11Colour Gold3 = opaque $ sRGB24 205 173 0 x11Colour Gold4 = opaque $ sRGB24 139 117 0 x11Colour Goldenrod = opaque $ sRGB24 218 165 32 x11Colour Goldenrod1 = opaque $ sRGB24 255 193 37 x11Colour Goldenrod2 = opaque $ sRGB24 238 180 34 x11Colour Goldenrod3 = opaque $ sRGB24 205 155 29 x11Colour Goldenrod4 = opaque $ sRGB24 139 105 20 x11Colour Gray = opaque $ sRGB24 192 192 192 x11Colour Gray0 = opaque $ sRGB24 0 0 0 x11Colour Gray1 = opaque $ sRGB24 3 3 3 x11Colour Gray2 = opaque $ sRGB24 5 5 5 x11Colour Gray3 = opaque $ sRGB24 8 8 8 x11Colour Gray4 = opaque $ sRGB24 10 10 10 x11Colour Gray5 = opaque $ sRGB24 13 13 13 x11Colour Gray6 = opaque $ sRGB24 15 15 15 x11Colour Gray7 = opaque $ sRGB24 18 18 18 x11Colour Gray8 = opaque $ sRGB24 20 20 20 x11Colour Gray9 = opaque $ sRGB24 23 23 23 x11Colour Gray10 = opaque $ sRGB24 26 26 26 x11Colour Gray11 = opaque $ sRGB24 28 28 28 x11Colour Gray12 = opaque $ sRGB24 31 31 31 x11Colour Gray13 = opaque $ sRGB24 33 33 33 x11Colour Gray14 = opaque $ sRGB24 36 36 36 x11Colour Gray15 = opaque $ sRGB24 38 38 38 x11Colour Gray16 = opaque $ sRGB24 41 41 41 x11Colour Gray17 = opaque $ sRGB24 43 43 43 x11Colour Gray18 = opaque $ sRGB24 46 46 46 x11Colour Gray19 = opaque $ sRGB24 48 48 48 x11Colour Gray20 = opaque $ sRGB24 51 51 51 x11Colour Gray21 = opaque $ sRGB24 54 54 54 x11Colour Gray22 = opaque $ sRGB24 56 56 56 x11Colour Gray23 = opaque $ sRGB24 59 59 59 x11Colour Gray24 = opaque $ sRGB24 61 61 61 x11Colour Gray25 = opaque $ sRGB24 64 64 64 x11Colour Gray26 = opaque $ sRGB24 66 66 66 x11Colour Gray27 = opaque $ sRGB24 69 69 69 x11Colour Gray28 = opaque $ sRGB24 71 71 71 x11Colour Gray29 = opaque $ sRGB24 74 74 74 x11Colour Gray30 = opaque $ sRGB24 77 77 77 x11Colour Gray31 = opaque $ sRGB24 79 79 79 x11Colour Gray32 = opaque $ sRGB24 82 82 82 x11Colour Gray33 = opaque $ sRGB24 84 84 84 x11Colour Gray34 = opaque $ sRGB24 87 87 87 x11Colour Gray35 = opaque $ sRGB24 89 89 89 x11Colour Gray36 = opaque $ sRGB24 92 92 92 x11Colour Gray37 = opaque $ sRGB24 94 94 94 x11Colour Gray38 = opaque $ sRGB24 97 97 97 x11Colour Gray39 = opaque $ sRGB24 99 99 99 x11Colour Gray40 = opaque $ sRGB24 102 102 102 x11Colour Gray41 = opaque $ sRGB24 105 105 105 x11Colour Gray42 = opaque $ sRGB24 107 107 107 x11Colour Gray43 = opaque $ sRGB24 110 110 110 x11Colour Gray44 = opaque $ sRGB24 112 112 112 x11Colour Gray45 = opaque $ sRGB24 115 115 115 x11Colour Gray46 = opaque $ sRGB24 117 117 117 x11Colour Gray47 = opaque $ sRGB24 120 120 120 x11Colour Gray48 = opaque $ sRGB24 122 122 122 x11Colour Gray49 = opaque $ sRGB24 125 125 125 x11Colour Gray50 = opaque $ sRGB24 127 127 127 x11Colour Gray51 = opaque $ sRGB24 130 130 130 x11Colour Gray52 = opaque $ sRGB24 133 133 133 x11Colour Gray53 = opaque $ sRGB24 135 135 135 x11Colour Gray54 = opaque $ sRGB24 138 138 138 x11Colour Gray55 = opaque $ sRGB24 140 140 140 x11Colour Gray56 = opaque $ sRGB24 143 143 143 x11Colour Gray57 = opaque $ sRGB24 145 145 145 x11Colour Gray58 = opaque $ sRGB24 148 148 148 x11Colour Gray59 = opaque $ sRGB24 150 150 150 x11Colour Gray60 = opaque $ sRGB24 153 153 153 x11Colour Gray61 = opaque $ sRGB24 156 156 156 x11Colour Gray62 = opaque $ sRGB24 158 158 158 x11Colour Gray63 = opaque $ sRGB24 161 161 161 x11Colour Gray64 = opaque $ sRGB24 163 163 163 x11Colour Gray65 = opaque $ sRGB24 166 166 166 x11Colour Gray66 = opaque $ sRGB24 168 168 168 x11Colour Gray67 = opaque $ sRGB24 171 171 171 x11Colour Gray68 = opaque $ sRGB24 173 173 173 x11Colour Gray69 = opaque $ sRGB24 176 176 176 x11Colour Gray70 = opaque $ sRGB24 179 179 179 x11Colour Gray71 = opaque $ sRGB24 181 181 181 x11Colour Gray72 = opaque $ sRGB24 184 184 184 x11Colour Gray73 = opaque $ sRGB24 186 186 186 x11Colour Gray74 = opaque $ sRGB24 189 189 189 x11Colour Gray75 = opaque $ sRGB24 191 191 191 x11Colour Gray76 = opaque $ sRGB24 194 194 194 x11Colour Gray77 = opaque $ sRGB24 196 196 196 x11Colour Gray78 = opaque $ sRGB24 199 199 199 x11Colour Gray79 = opaque $ sRGB24 201 201 201 x11Colour Gray80 = opaque $ sRGB24 204 204 204 x11Colour Gray81 = opaque $ sRGB24 207 207 207 x11Colour Gray82 = opaque $ sRGB24 209 209 209 x11Colour Gray83 = opaque $ sRGB24 212 212 212 x11Colour Gray84 = opaque $ sRGB24 214 214 214 x11Colour Gray85 = opaque $ sRGB24 217 217 217 x11Colour Gray86 = opaque $ sRGB24 219 219 219 x11Colour Gray87 = opaque $ sRGB24 222 222 222 x11Colour Gray88 = opaque $ sRGB24 224 224 224 x11Colour Gray89 = opaque $ sRGB24 227 227 227 x11Colour Gray90 = opaque $ sRGB24 229 229 229 x11Colour Gray91 = opaque $ sRGB24 232 232 232 x11Colour Gray92 = opaque $ sRGB24 235 235 235 x11Colour Gray93 = opaque $ sRGB24 237 237 237 x11Colour Gray94 = opaque $ sRGB24 240 240 240 x11Colour Gray95 = opaque $ sRGB24 242 242 242 x11Colour Gray96 = opaque $ sRGB24 245 245 245 x11Colour Gray97 = opaque $ sRGB24 247 247 247 x11Colour Gray98 = opaque $ sRGB24 250 250 250 x11Colour Gray99 = opaque $ sRGB24 252 252 252 x11Colour Gray100 = opaque $ sRGB24 255 255 255 x11Colour Green = opaque $ sRGB24 0 255 0 x11Colour Green1 = opaque $ sRGB24 0 255 0 x11Colour Green2 = opaque $ sRGB24 0 238 0 x11Colour Green3 = opaque $ sRGB24 0 205 0 x11Colour Green4 = opaque $ sRGB24 0 139 0 x11Colour GreenYellow = opaque $ sRGB24 173 255 47 x11Colour HoneyDew = opaque $ sRGB24 240 255 240 x11Colour HoneyDew1 = opaque $ sRGB24 240 255 240 x11Colour HoneyDew2 = opaque $ sRGB24 224 238 224 x11Colour HoneyDew3 = opaque $ sRGB24 193 205 193 x11Colour HoneyDew4 = opaque $ sRGB24 131 139 131 x11Colour HotPink = opaque $ sRGB24 255 105 180 x11Colour HotPink1 = opaque $ sRGB24 255 110 180 x11Colour HotPink2 = opaque $ sRGB24 238 106 167 x11Colour HotPink3 = opaque $ sRGB24 205 96 144 x11Colour HotPink4 = opaque $ sRGB24 139 58 98 x11Colour IndianRed = opaque $ sRGB24 205 92 92 x11Colour IndianRed1 = opaque $ sRGB24 255 106 106 x11Colour IndianRed2 = opaque $ sRGB24 238 99 99 x11Colour IndianRed3 = opaque $ sRGB24 205 85 85 x11Colour IndianRed4 = opaque $ sRGB24 139 58 58 x11Colour Indigo = opaque $ sRGB24 75 0 130 x11Colour Ivory = opaque $ sRGB24 255 255 240 x11Colour Ivory1 = opaque $ sRGB24 255 255 240 x11Colour Ivory2 = opaque $ sRGB24 238 238 224 x11Colour Ivory3 = opaque $ sRGB24 205 205 193 x11Colour Ivory4 = opaque $ sRGB24 139 139 131 x11Colour Khaki = opaque $ sRGB24 240 230 140 x11Colour Khaki1 = opaque $ sRGB24 255 246 143 x11Colour Khaki2 = opaque $ sRGB24 238 230 133 x11Colour Khaki3 = opaque $ sRGB24 205 198 115 x11Colour Khaki4 = opaque $ sRGB24 139 134 78 x11Colour Lavender = opaque $ sRGB24 230 230 250 x11Colour LavenderBlush = opaque $ sRGB24 255 240 245 x11Colour LavenderBlush1 = opaque $ sRGB24 255 240 245 x11Colour LavenderBlush2 = opaque $ sRGB24 238 224 229 x11Colour LavenderBlush3 = opaque $ sRGB24 205 193 197 x11Colour LavenderBlush4 = opaque $ sRGB24 139 131 134 x11Colour LawnGreen = opaque $ sRGB24 124 252 0 x11Colour LemonChiffon = opaque $ sRGB24 255 250 205 x11Colour LemonChiffon1 = opaque $ sRGB24 255 250 205 x11Colour LemonChiffon2 = opaque $ sRGB24 238 233 191 x11Colour LemonChiffon3 = opaque $ sRGB24 205 201 165 x11Colour LemonChiffon4 = opaque $ sRGB24 139 137 112 x11Colour LightBlue = opaque $ sRGB24 173 216 230 x11Colour LightBlue1 = opaque $ sRGB24 191 239 255 x11Colour LightBlue2 = opaque $ sRGB24 178 223 238 x11Colour LightBlue3 = opaque $ sRGB24 154 192 205 x11Colour LightBlue4 = opaque $ sRGB24 104 131 139 x11Colour LightCoral = opaque $ sRGB24 240 128 128 x11Colour LightCyan = opaque $ sRGB24 224 255 255 x11Colour LightCyan1 = opaque $ sRGB24 224 255 255 x11Colour LightCyan2 = opaque $ sRGB24 209 238 238 x11Colour LightCyan3 = opaque $ sRGB24 180 205 205 x11Colour LightCyan4 = opaque $ sRGB24 122 139 139 x11Colour LightGoldenrod = opaque $ sRGB24 238 221 130 x11Colour LightGoldenrod1 = opaque $ sRGB24 255 236 139 x11Colour LightGoldenrod2 = opaque $ sRGB24 238 220 130 x11Colour LightGoldenrod3 = opaque $ sRGB24 205 190 112 x11Colour LightGoldenrod4 = opaque $ sRGB24 139 129 76 x11Colour LightGoldenrodYellow = opaque $ sRGB24 250 250 210 x11Colour LightGray = opaque $ sRGB24 211 211 211 x11Colour LightPink = opaque $ sRGB24 255 182 193 x11Colour LightPink1 = opaque $ sRGB24 255 174 185 x11Colour LightPink2 = opaque $ sRGB24 238 162 173 x11Colour LightPink3 = opaque $ sRGB24 205 140 149 x11Colour LightPink4 = opaque $ sRGB24 139 95 101 x11Colour LightSalmon = opaque $ sRGB24 255 160 122 x11Colour LightSalmon1 = opaque $ sRGB24 255 160 122 x11Colour LightSalmon2 = opaque $ sRGB24 238 149 114 x11Colour LightSalmon3 = opaque $ sRGB24 205 129 98 x11Colour LightSalmon4 = opaque $ sRGB24 139 87 66 x11Colour LightSeaGreen = opaque $ sRGB24 32 178 170 x11Colour LightSkyBlue = opaque $ sRGB24 135 206 250 x11Colour LightSkyBlue1 = opaque $ sRGB24 176 226 255 x11Colour LightSkyBlue2 = opaque $ sRGB24 164 211 238 x11Colour LightSkyBlue3 = opaque $ sRGB24 141 182 205 x11Colour LightSkyBlue4 = opaque $ sRGB24 96 123 139 x11Colour LightSlateBlue = opaque $ sRGB24 132 112 255 x11Colour LightSlateGray = opaque $ sRGB24 119 136 153 x11Colour LightSteelBlue = opaque $ sRGB24 176 196 222 x11Colour LightSteelBlue1 = opaque $ sRGB24 202 225 255 x11Colour LightSteelBlue2 = opaque $ sRGB24 188 210 238 x11Colour LightSteelBlue3 = opaque $ sRGB24 162 181 205 x11Colour LightSteelBlue4 = opaque $ sRGB24 110 123 139 x11Colour LightYellow = opaque $ sRGB24 255 255 224 x11Colour LightYellow1 = opaque $ sRGB24 255 255 224 x11Colour LightYellow2 = opaque $ sRGB24 238 238 209 x11Colour LightYellow3 = opaque $ sRGB24 205 205 180 x11Colour LightYellow4 = opaque $ sRGB24 139 139 122 x11Colour LimeGreen = opaque $ sRGB24 50 205 50 x11Colour Linen = opaque $ sRGB24 250 240 230 x11Colour Magenta = opaque $ sRGB24 255 0 255 x11Colour Magenta1 = opaque $ sRGB24 255 0 255 x11Colour Magenta2 = opaque $ sRGB24 238 0 238 x11Colour Magenta3 = opaque $ sRGB24 205 0 205 x11Colour Magenta4 = opaque $ sRGB24 139 0 139 x11Colour Maroon = opaque $ sRGB24 176 48 96 x11Colour Maroon1 = opaque $ sRGB24 255 52 179 x11Colour Maroon2 = opaque $ sRGB24 238 48 167 x11Colour Maroon3 = opaque $ sRGB24 205 41 144 x11Colour Maroon4 = opaque $ sRGB24 139 28 98 x11Colour MediumAquamarine = opaque $ sRGB24 102 205 170 x11Colour MediumBlue = opaque $ sRGB24 0 0 205 x11Colour MediumOrchid = opaque $ sRGB24 186 85 211 x11Colour MediumOrchid1 = opaque $ sRGB24 224 102 255 x11Colour MediumOrchid2 = opaque $ sRGB24 209 95 238 x11Colour MediumOrchid3 = opaque $ sRGB24 180 82 205 x11Colour MediumOrchid4 = opaque $ sRGB24 122 55 139 x11Colour MediumPurple = opaque $ sRGB24 147 112 219 x11Colour MediumPurple1 = opaque $ sRGB24 171 130 255 x11Colour MediumPurple2 = opaque $ sRGB24 159 121 238 x11Colour MediumPurple3 = opaque $ sRGB24 137 104 205 x11Colour MediumPurple4 = opaque $ sRGB24 93 71 139 x11Colour MediumSeaGreen = opaque $ sRGB24 60 179 113 x11Colour MediumSlateBlue = opaque $ sRGB24 123 104 238 x11Colour MediumSpringGreen = opaque $ sRGB24 0 250 154 x11Colour MediumTurquoise = opaque $ sRGB24 72 209 204 x11Colour MediumVioletRed = opaque $ sRGB24 199 21 133 x11Colour MidnightBlue = opaque $ sRGB24 25 25 112 x11Colour MintCream = opaque $ sRGB24 245 255 250 x11Colour MistyRose = opaque $ sRGB24 255 228 225 x11Colour MistyRose1 = opaque $ sRGB24 255 228 225 x11Colour MistyRose2 = opaque $ sRGB24 238 213 210 x11Colour MistyRose3 = opaque $ sRGB24 205 183 181 x11Colour MistyRose4 = opaque $ sRGB24 139 125 123 x11Colour Moccasin = opaque $ sRGB24 255 228 181 x11Colour NavajoWhite = opaque $ sRGB24 255 222 173 x11Colour NavajoWhite1 = opaque $ sRGB24 255 222 173 x11Colour NavajoWhite2 = opaque $ sRGB24 238 207 161 x11Colour NavajoWhite3 = opaque $ sRGB24 205 179 139 x11Colour NavajoWhite4 = opaque $ sRGB24 139 121 94 x11Colour Navy = opaque $ sRGB24 0 0 128 x11Colour NavyBlue = opaque $ sRGB24 0 0 128 x11Colour OldLace = opaque $ sRGB24 253 245 230 x11Colour OliveDrab = opaque $ sRGB24 107 142 35 x11Colour OliveDrab1 = opaque $ sRGB24 192 255 62 x11Colour OliveDrab2 = opaque $ sRGB24 179 238 58 x11Colour OliveDrab3 = opaque $ sRGB24 154 205 50 x11Colour OliveDrab4 = opaque $ sRGB24 105 139 34 x11Colour Orange = opaque $ sRGB24 255 165 0 x11Colour Orange1 = opaque $ sRGB24 255 165 0 x11Colour Orange2 = opaque $ sRGB24 238 154 0 x11Colour Orange3 = opaque $ sRGB24 205 133 0 x11Colour Orange4 = opaque $ sRGB24 139 90 0 x11Colour OrangeRed = opaque $ sRGB24 255 69 0 x11Colour OrangeRed1 = opaque $ sRGB24 255 69 0 x11Colour OrangeRed2 = opaque $ sRGB24 238 64 0 x11Colour OrangeRed3 = opaque $ sRGB24 205 55 0 x11Colour OrangeRed4 = opaque $ sRGB24 139 37 0 x11Colour Orchid = opaque $ sRGB24 218 112 214 x11Colour Orchid1 = opaque $ sRGB24 255 131 250 x11Colour Orchid2 = opaque $ sRGB24 238 122 233 x11Colour Orchid3 = opaque $ sRGB24 205 105 201 x11Colour Orchid4 = opaque $ sRGB24 139 71 137 x11Colour PaleGoldenrod = opaque $ sRGB24 238 232 170 x11Colour PaleGreen = opaque $ sRGB24 152 251 152 x11Colour PaleGreen1 = opaque $ sRGB24 154 255 154 x11Colour PaleGreen2 = opaque $ sRGB24 144 238 144 x11Colour PaleGreen3 = opaque $ sRGB24 124 205 124 x11Colour PaleGreen4 = opaque $ sRGB24 84 139 84 x11Colour PaleTurquoise = opaque $ sRGB24 175 238 238 x11Colour PaleTurquoise1 = opaque $ sRGB24 187 255 255 x11Colour PaleTurquoise2 = opaque $ sRGB24 174 238 238 x11Colour PaleTurquoise3 = opaque $ sRGB24 150 205 205 x11Colour PaleTurquoise4 = opaque $ sRGB24 102 139 139 x11Colour PaleVioletRed = opaque $ sRGB24 219 112 147 x11Colour PaleVioletRed1 = opaque $ sRGB24 255 130 171 x11Colour PaleVioletRed2 = opaque $ sRGB24 238 121 159 x11Colour PaleVioletRed3 = opaque $ sRGB24 205 104 137 x11Colour PaleVioletRed4 = opaque $ sRGB24 139 71 93 x11Colour PapayaWhip = opaque $ sRGB24 255 239 213 x11Colour PeachPuff = opaque $ sRGB24 255 218 185 x11Colour PeachPuff1 = opaque $ sRGB24 255 218 185 x11Colour PeachPuff2 = opaque $ sRGB24 238 203 173 x11Colour PeachPuff3 = opaque $ sRGB24 205 175 149 x11Colour PeachPuff4 = opaque $ sRGB24 139 119 101 x11Colour Peru = opaque $ sRGB24 205 133 63 x11Colour Pink = opaque $ sRGB24 255 192 203 x11Colour Pink1 = opaque $ sRGB24 255 181 197 x11Colour Pink2 = opaque $ sRGB24 238 169 184 x11Colour Pink3 = opaque $ sRGB24 205 145 158 x11Colour Pink4 = opaque $ sRGB24 139 99 108 x11Colour Plum = opaque $ sRGB24 221 160 221 x11Colour Plum1 = opaque $ sRGB24 255 187 255 x11Colour Plum2 = opaque $ sRGB24 238 174 238 x11Colour Plum3 = opaque $ sRGB24 205 150 205 x11Colour Plum4 = opaque $ sRGB24 139 102 139 x11Colour PowderBlue = opaque $ sRGB24 176 224 230 x11Colour Purple = opaque $ sRGB24 160 32 240 x11Colour Purple1 = opaque $ sRGB24 155 48 255 x11Colour Purple2 = opaque $ sRGB24 145 44 238 x11Colour Purple3 = opaque $ sRGB24 125 38 205 x11Colour Purple4 = opaque $ sRGB24 85 26 139 x11Colour Red = opaque $ sRGB24 255 0 0 x11Colour Red1 = opaque $ sRGB24 255 0 0 x11Colour Red2 = opaque $ sRGB24 238 0 0 x11Colour Red3 = opaque $ sRGB24 205 0 0 x11Colour Red4 = opaque $ sRGB24 139 0 0 x11Colour RosyBrown = opaque $ sRGB24 188 143 143 x11Colour RosyBrown1 = opaque $ sRGB24 255 193 193 x11Colour RosyBrown2 = opaque $ sRGB24 238 180 180 x11Colour RosyBrown3 = opaque $ sRGB24 205 155 155 x11Colour RosyBrown4 = opaque $ sRGB24 139 105 105 x11Colour RoyalBlue = opaque $ sRGB24 65 105 225 x11Colour RoyalBlue1 = opaque $ sRGB24 72 118 255 x11Colour RoyalBlue2 = opaque $ sRGB24 67 110 238 x11Colour RoyalBlue3 = opaque $ sRGB24 58 95 205 x11Colour RoyalBlue4 = opaque $ sRGB24 39 64 139 x11Colour SaddleBrown = opaque $ sRGB24 139 69 19 x11Colour Salmon = opaque $ sRGB24 250 128 114 x11Colour Salmon1 = opaque $ sRGB24 255 140 105 x11Colour Salmon2 = opaque $ sRGB24 238 130 98 x11Colour Salmon3 = opaque $ sRGB24 205 112 84 x11Colour Salmon4 = opaque $ sRGB24 139 76 57 x11Colour SandyBrown = opaque $ sRGB24 244 164 96 x11Colour SeaGreen = opaque $ sRGB24 46 139 87 x11Colour SeaGreen1 = opaque $ sRGB24 84 255 159 x11Colour SeaGreen2 = opaque $ sRGB24 78 238 148 x11Colour SeaGreen3 = opaque $ sRGB24 67 205 128 x11Colour SeaGreen4 = opaque $ sRGB24 46 139 87 x11Colour SeaShell = opaque $ sRGB24 255 245 238 x11Colour SeaShell1 = opaque $ sRGB24 255 245 238 x11Colour SeaShell2 = opaque $ sRGB24 238 229 222 x11Colour SeaShell3 = opaque $ sRGB24 205 197 191 x11Colour SeaShell4 = opaque $ sRGB24 139 134 130 x11Colour Sienna = opaque $ sRGB24 160 82 45 x11Colour Sienna1 = opaque $ sRGB24 255 130 71 x11Colour Sienna2 = opaque $ sRGB24 238 121 66 x11Colour Sienna3 = opaque $ sRGB24 205 104 57 x11Colour Sienna4 = opaque $ sRGB24 139 71 38 x11Colour SkyBlue = opaque $ sRGB24 135 206 235 x11Colour SkyBlue1 = opaque $ sRGB24 135 206 255 x11Colour SkyBlue2 = opaque $ sRGB24 126 192 238 x11Colour SkyBlue3 = opaque $ sRGB24 108 166 205 x11Colour SkyBlue4 = opaque $ sRGB24 74 112 139 x11Colour SlateBlue = opaque $ sRGB24 106 90 205 x11Colour SlateBlue1 = opaque $ sRGB24 131 111 255 x11Colour SlateBlue2 = opaque $ sRGB24 122 103 238 x11Colour SlateBlue3 = opaque $ sRGB24 105 89 205 x11Colour SlateBlue4 = opaque $ sRGB24 71 60 139 x11Colour SlateGray = opaque $ sRGB24 112 128 144 x11Colour SlateGray1 = opaque $ sRGB24 198 226 255 x11Colour SlateGray2 = opaque $ sRGB24 185 211 238 x11Colour SlateGray3 = opaque $ sRGB24 159 182 205 x11Colour SlateGray4 = opaque $ sRGB24 108 123 139 x11Colour Snow = opaque $ sRGB24 255 250 250 x11Colour Snow1 = opaque $ sRGB24 255 250 250 x11Colour Snow2 = opaque $ sRGB24 238 233 233 x11Colour Snow3 = opaque $ sRGB24 205 201 201 x11Colour Snow4 = opaque $ sRGB24 139 137 137 x11Colour SpringGreen = opaque $ sRGB24 0 255 127 x11Colour SpringGreen1 = opaque $ sRGB24 0 255 127 x11Colour SpringGreen2 = opaque $ sRGB24 0 238 118 x11Colour SpringGreen3 = opaque $ sRGB24 0 205 102 x11Colour SpringGreen4 = opaque $ sRGB24 0 139 69 x11Colour SteelBlue = opaque $ sRGB24 70 130 180 x11Colour SteelBlue1 = opaque $ sRGB24 99 184 255 x11Colour SteelBlue2 = opaque $ sRGB24 92 172 238 x11Colour SteelBlue3 = opaque $ sRGB24 79 148 205 x11Colour SteelBlue4 = opaque $ sRGB24 54 100 139 x11Colour Tan = opaque $ sRGB24 210 180 140 x11Colour Tan1 = opaque $ sRGB24 255 165 79 x11Colour Tan2 = opaque $ sRGB24 238 154 73 x11Colour Tan3 = opaque $ sRGB24 205 133 63 x11Colour Tan4 = opaque $ sRGB24 139 90 43 x11Colour Thistle = opaque $ sRGB24 216 191 216 x11Colour Thistle1 = opaque $ sRGB24 255 225 255 x11Colour Thistle2 = opaque $ sRGB24 238 210 238 x11Colour Thistle3 = opaque $ sRGB24 205 181 205 x11Colour Thistle4 = opaque $ sRGB24 139 123 139 x11Colour Tomato = opaque $ sRGB24 255 99 71 x11Colour Tomato1 = opaque $ sRGB24 255 99 71 x11Colour Tomato2 = opaque $ sRGB24 238 92 66 x11Colour Tomato3 = opaque $ sRGB24 205 79 57 x11Colour Tomato4 = opaque $ sRGB24 139 54 38 x11Colour Transparent = transparent x11Colour Turquoise = opaque $ sRGB24 64 224 208 x11Colour Turquoise1 = opaque $ sRGB24 0 245 255 x11Colour Turquoise2 = opaque $ sRGB24 0 229 238 x11Colour Turquoise3 = opaque $ sRGB24 0 197 205 x11Colour Turquoise4 = opaque $ sRGB24 0 134 139 x11Colour Violet = opaque $ sRGB24 238 130 238 x11Colour VioletRed = opaque $ sRGB24 208 32 144 x11Colour VioletRed1 = opaque $ sRGB24 255 62 150 x11Colour VioletRed2 = opaque $ sRGB24 238 58 140 x11Colour VioletRed3 = opaque $ sRGB24 205 50 120 x11Colour VioletRed4 = opaque $ sRGB24 139 34 82 x11Colour Wheat = opaque $ sRGB24 245 222 179 x11Colour Wheat1 = opaque $ sRGB24 255 231 186 x11Colour Wheat2 = opaque $ sRGB24 238 216 174 x11Colour Wheat3 = opaque $ sRGB24 205 186 150 x11Colour Wheat4 = opaque $ sRGB24 139 126 102 x11Colour White = opaque $ sRGB24 255 255 255 x11Colour WhiteSmoke = opaque $ sRGB24 245 245 245 x11Colour Yellow = opaque $ sRGB24 255 255 0 x11Colour Yellow1 = opaque $ sRGB24 255 255 0 x11Colour Yellow2 = opaque $ sRGB24 238 238 0 x11Colour Yellow3 = opaque $ sRGB24 205 205 0 x11Colour Yellow4 = opaque $ sRGB24 139 139 0 x11Colour YellowGreen = opaque $ sRGB24 154 205 50 graphviz-2999.20.2.0/Data/GraphViz/Attributes/Colors/Brewer.hs0000644000000000000000000000307314535166704022020 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {- | Module : Data.GraphViz.Attributes.Colors.Brewer Description : Specification of Brewer colors. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com You almost definitely do /not/ want to use this module. It is only defined for completeness when parsing existing Dot code. Graphviz contains a list of colors known as the /Brewer color schemes/. These colors are available under an Apache-style license: . As such, they are not recommended for general use, and have only been included in this package for completeness. The complete list of Brewer colors can be found at . -} module Data.GraphViz.Attributes.Colors.Brewer ( BrewerScheme(..) , BrewerName(..) , BrewerColor(..) ) where {- This is a virtual module designed just to re-export the Brewer colors. -} import Data.GraphViz.Attributes.ColorScheme(BrewerScheme(..), BrewerName(..)) -- To get the instances import Data.GraphViz.Parsing() import Data.GraphViz.Printing() import Data.Word(Word8) -- ----------------------------------------------------------------------------- -- Note: we do /not/ have {Print,Parse}Dot instances for this; it's covered in Color. -- | This value should be between @1@ and the level of the -- 'BrewerScheme' being used. data BrewerColor = BC BrewerScheme Word8 deriving (Eq, Ord, Show, Read) graphviz-2999.20.2.0/Data/GraphViz/Attributes/Colors/SVG.hs0000644000000000000000000006547614535166704021250 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {- | Module : Data.GraphViz.Attributes.Colors.SVG Description : Specification of SVG colors. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com Graphviz comes with an SVG color scheme: However, in general use you probably want to use "Data.GraphViz.Attributes.Colors.X11" instead, unless you are only generating SVG images. -} module Data.GraphViz.Attributes.Colors.SVG ( SVGColor(..) , svgColour ) where import Data.GraphViz.Parsing import Data.GraphViz.Printing import Data.Colour(Colour) import Data.Colour.SRGB(sRGB24) -- ----------------------------------------------------------------------------- -- | The SVG colors that Graphviz uses. Graphviz's list of colors -- also duplicated all @*Gray*@ colors with @*Grey*@ ones; parsing -- of an 'SVGColor' which is specified using \"grey\" will succeed. data SVGColor = AliceBlue | AntiqueWhite | Aqua | Aquamarine | Azure | Beige | Bisque | Black | BlanchedAlmond | Blue | BlueViolet | Brown | Burlywood | CadetBlue | Chartreuse | Chocolate | Coral | CornflowerBlue | Cornsilk | Crimson | Cyan | DarkBlue | DarkCyan | DarkGoldenrod | DarkGray | DarkGreen | DarkKhaki | DarkMagenta | DarkOliveGreen | DarkOrange | DarkOrchid | DarkRed | DarkSalmon | DarkSeaGreen | DarkSlateBlue | DarkSlateGray | DarkTurquoise | DarkViolet | DeepPink | DeepSkyBlue | DimGray | DodgerBlue | Firebrick | FloralWhite | ForestGreen | Fuchsia | Gainsboro | GhostWhite | Gold | Goldenrod | Gray | Green | GreenYellow | Honeydew | HotPink | IndianRed | Indigo | Ivory | Khaki | Lavender | LavenderBlush | LawnGreen | LemonChiffon | LightBlue | LightCoral | LightCyan | LightGoldenrodYellow | LightGray | LightGreen | LightPink | LightSalmon | LightSeaGreen | LightSkyBlue | LightSlateGray | LightSteelBlue | LightYellow | Lime | LimeGreen | Linen | Magenta | Maroon | MediumAquamarine | MediumBlue | MediumOrchid | MediumPurple | MediumSeaGreen | MediumSlateBlue | MediumSpringGreen | MediumTurquoise | MediumVioletRed | MidnightBlue | MintCream | MistyRose | Moccasin | NavajoWhite | Navy | OldLace | Olive | OliveDrab | Orange | OrangeRed | Orchid | PaleGoldenrod | PaleGreen | PaleTurquoise | PaleVioletRed | PapayaWhip | PeachPuff | Peru | Pink | Plum | PowderBlue | Purple | Red | RosyBrown | RoyalBlue | SaddleBrown | Salmon | SandyBrown | SeaGreen | SeaShell | Sienna | Silver | SkyBlue | SlateBlue | SlateGray | Snow | SpringGreen | SteelBlue | Tan | Teal | Thistle | Tomato | Turquoise | Violet | Wheat | White | WhiteSmoke | Yellow | YellowGreen deriving (Eq, Ord, Bounded, Enum, Show, Read) instance PrintDot SVGColor where unqtDot AliceBlue = unqtText "aliceblue" unqtDot AntiqueWhite = unqtText "antiquewhite" unqtDot Aqua = unqtText "aqua" unqtDot Aquamarine = unqtText "aquamarine" unqtDot Azure = unqtText "azure" unqtDot Beige = unqtText "beige" unqtDot Bisque = unqtText "bisque" unqtDot Black = unqtText "black" unqtDot BlanchedAlmond = unqtText "blanchedalmond" unqtDot Blue = unqtText "blue" unqtDot BlueViolet = unqtText "blueviolet" unqtDot Brown = unqtText "brown" unqtDot Burlywood = unqtText "burlywood" unqtDot CadetBlue = unqtText "cadetblue" unqtDot Chartreuse = unqtText "chartreuse" unqtDot Chocolate = unqtText "chocolate" unqtDot Coral = unqtText "coral" unqtDot CornflowerBlue = unqtText "cornflowerblue" unqtDot Cornsilk = unqtText "cornsilk" unqtDot Crimson = unqtText "crimson" unqtDot Cyan = unqtText "cyan" unqtDot DarkBlue = unqtText "darkblue" unqtDot DarkCyan = unqtText "darkcyan" unqtDot DarkGoldenrod = unqtText "darkgoldenrod" unqtDot DarkGray = unqtText "darkgray" unqtDot DarkGreen = unqtText "darkgreen" unqtDot DarkKhaki = unqtText "darkkhaki" unqtDot DarkMagenta = unqtText "darkmagenta" unqtDot DarkOliveGreen = unqtText "darkolivegreen" unqtDot DarkOrange = unqtText "darkorange" unqtDot DarkOrchid = unqtText "darkorchid" unqtDot DarkRed = unqtText "darkred" unqtDot DarkSalmon = unqtText "darksalmon" unqtDot DarkSeaGreen = unqtText "darkseagreen" unqtDot DarkSlateBlue = unqtText "darkslateblue" unqtDot DarkSlateGray = unqtText "darkslategray" unqtDot DarkTurquoise = unqtText "darkturquoise" unqtDot DarkViolet = unqtText "darkviolet" unqtDot DeepPink = unqtText "deeppink" unqtDot DeepSkyBlue = unqtText "deepskyblue" unqtDot DimGray = unqtText "dimgray" unqtDot DodgerBlue = unqtText "dodgerblue" unqtDot Firebrick = unqtText "firebrick" unqtDot FloralWhite = unqtText "floralwhite" unqtDot ForestGreen = unqtText "forestgreen" unqtDot Fuchsia = unqtText "fuchsia" unqtDot Gainsboro = unqtText "gainsboro" unqtDot GhostWhite = unqtText "ghostwhite" unqtDot Gold = unqtText "gold" unqtDot Goldenrod = unqtText "goldenrod" unqtDot Gray = unqtText "gray" unqtDot Green = unqtText "green" unqtDot GreenYellow = unqtText "greenyellow" unqtDot Honeydew = unqtText "honeydew" unqtDot HotPink = unqtText "hotpink" unqtDot IndianRed = unqtText "indianred" unqtDot Indigo = unqtText "indigo" unqtDot Ivory = unqtText "ivory" unqtDot Khaki = unqtText "khaki" unqtDot Lavender = unqtText "lavender" unqtDot LavenderBlush = unqtText "lavenderblush" unqtDot LawnGreen = unqtText "lawngreen" unqtDot LemonChiffon = unqtText "lemonchiffon" unqtDot LightBlue = unqtText "lightblue" unqtDot LightCoral = unqtText "lightcoral" unqtDot LightCyan = unqtText "lightcyan" unqtDot LightGoldenrodYellow = unqtText "lightgoldenrodyellow" unqtDot LightGray = unqtText "lightgray" unqtDot LightGreen = unqtText "lightgreen" unqtDot LightPink = unqtText "lightpink" unqtDot LightSalmon = unqtText "lightsalmon" unqtDot LightSeaGreen = unqtText "lightseagreen" unqtDot LightSkyBlue = unqtText "lightskyblue" unqtDot LightSlateGray = unqtText "lightslategray" unqtDot LightSteelBlue = unqtText "lightsteelblue" unqtDot LightYellow = unqtText "lightyellow" unqtDot Lime = unqtText "lime" unqtDot LimeGreen = unqtText "limegreen" unqtDot Linen = unqtText "linen" unqtDot Magenta = unqtText "magenta" unqtDot Maroon = unqtText "maroon" unqtDot MediumAquamarine = unqtText "mediumaquamarine" unqtDot MediumBlue = unqtText "mediumblue" unqtDot MediumOrchid = unqtText "mediumorchid" unqtDot MediumPurple = unqtText "mediumpurple" unqtDot MediumSeaGreen = unqtText "mediumseagreen" unqtDot MediumSlateBlue = unqtText "mediumslateblue" unqtDot MediumSpringGreen = unqtText "mediumspringgreen" unqtDot MediumTurquoise = unqtText "mediumturquoise" unqtDot MediumVioletRed = unqtText "mediumvioletred" unqtDot MidnightBlue = unqtText "midnightblue" unqtDot MintCream = unqtText "mintcream" unqtDot MistyRose = unqtText "mistyrose" unqtDot Moccasin = unqtText "moccasin" unqtDot NavajoWhite = unqtText "navajowhite" unqtDot Navy = unqtText "navy" unqtDot OldLace = unqtText "oldlace" unqtDot Olive = unqtText "olive" unqtDot OliveDrab = unqtText "olivedrab" unqtDot Orange = unqtText "orange" unqtDot OrangeRed = unqtText "orangered" unqtDot Orchid = unqtText "orchid" unqtDot PaleGoldenrod = unqtText "palegoldenrod" unqtDot PaleGreen = unqtText "palegreen" unqtDot PaleTurquoise = unqtText "paleturquoise" unqtDot PaleVioletRed = unqtText "palevioletred" unqtDot PapayaWhip = unqtText "papayawhip" unqtDot PeachPuff = unqtText "peachpuff" unqtDot Peru = unqtText "peru" unqtDot Pink = unqtText "pink" unqtDot Plum = unqtText "plum" unqtDot PowderBlue = unqtText "powderblue" unqtDot Purple = unqtText "purple" unqtDot Red = unqtText "red" unqtDot RosyBrown = unqtText "rosybrown" unqtDot RoyalBlue = unqtText "royalblue" unqtDot SaddleBrown = unqtText "saddlebrown" unqtDot Salmon = unqtText "salmon" unqtDot SandyBrown = unqtText "sandybrown" unqtDot SeaGreen = unqtText "seagreen" unqtDot SeaShell = unqtText "seashell" unqtDot Sienna = unqtText "sienna" unqtDot Silver = unqtText "silver" unqtDot SkyBlue = unqtText "skyblue" unqtDot SlateBlue = unqtText "slateblue" unqtDot SlateGray = unqtText "slategray" unqtDot Snow = unqtText "snow" unqtDot SpringGreen = unqtText "springgreen" unqtDot SteelBlue = unqtText "steelblue" unqtDot Tan = unqtText "tan" unqtDot Teal = unqtText "teal" unqtDot Thistle = unqtText "thistle" unqtDot Tomato = unqtText "tomato" unqtDot Turquoise = unqtText "turquoise" unqtDot Violet = unqtText "violet" unqtDot Wheat = unqtText "wheat" unqtDot White = unqtText "white" unqtDot WhiteSmoke = unqtText "whitesmoke" unqtDot Yellow = unqtText "yellow" unqtDot YellowGreen = unqtText "yellowgreen" instance ParseDot SVGColor where parseUnqt = stringValue [ ("aliceblue", AliceBlue) , ("antiquewhite", AntiqueWhite) , ("aqua", Aqua) , ("aquamarine", Aquamarine) , ("azure", Azure) , ("beige", Beige) , ("bisque", Bisque) , ("black", Black) , ("blanchedalmond", BlanchedAlmond) , ("blue", Blue) , ("blueviolet", BlueViolet) , ("brown", Brown) , ("burlywood", Burlywood) , ("cadetblue", CadetBlue) , ("chartreuse", Chartreuse) , ("chocolate", Chocolate) , ("coral", Coral) , ("cornflowerblue", CornflowerBlue) , ("cornsilk", Cornsilk) , ("crimson", Crimson) , ("cyan", Cyan) , ("darkblue", DarkBlue) , ("darkcyan", DarkCyan) , ("darkgoldenrod", DarkGoldenrod) , ("darkgray", DarkGray) , ("darkgrey", DarkGray) , ("darkgreen", DarkGreen) , ("darkkhaki", DarkKhaki) , ("darkmagenta", DarkMagenta) , ("darkolivegreen", DarkOliveGreen) , ("darkorange", DarkOrange) , ("darkorchid", DarkOrchid) , ("darkred", DarkRed) , ("darksalmon", DarkSalmon) , ("darkseagreen", DarkSeaGreen) , ("darkslateblue", DarkSlateBlue) , ("darkslategray", DarkSlateGray) , ("darkslategrey", DarkSlateGray) , ("darkturquoise", DarkTurquoise) , ("darkviolet", DarkViolet) , ("deeppink", DeepPink) , ("deepskyblue", DeepSkyBlue) , ("dimgray", DimGray) , ("dimgrey", DimGray) , ("dodgerblue", DodgerBlue) , ("firebrick", Firebrick) , ("floralwhite", FloralWhite) , ("forestgreen", ForestGreen) , ("fuchsia", Fuchsia) , ("gainsboro", Gainsboro) , ("ghostwhite", GhostWhite) , ("gold", Gold) , ("goldenrod", Goldenrod) , ("gray", Gray) , ("grey", Gray) , ("green", Green) , ("greenyellow", GreenYellow) , ("honeydew", Honeydew) , ("hotpink", HotPink) , ("indianred", IndianRed) , ("indigo", Indigo) , ("ivory", Ivory) , ("khaki", Khaki) , ("lavender", Lavender) , ("lavenderblush", LavenderBlush) , ("lawngreen", LawnGreen) , ("lemonchiffon", LemonChiffon) , ("lightblue", LightBlue) , ("lightcoral", LightCoral) , ("lightcyan", LightCyan) , ("lightgoldenrodyellow", LightGoldenrodYellow) , ("lightgray", LightGray) , ("lightgrey", LightGray) , ("lightgreen", LightGreen) , ("lightpink", LightPink) , ("lightsalmon", LightSalmon) , ("lightseagreen", LightSeaGreen) , ("lightskyblue", LightSkyBlue) , ("lightslategray", LightSlateGray) , ("lightslategrey", LightSlateGray) , ("lightsteelblue", LightSteelBlue) , ("lightyellow", LightYellow) , ("lime", Lime) , ("limegreen", LimeGreen) , ("linen", Linen) , ("magenta", Magenta) , ("maroon", Maroon) , ("mediumaquamarine", MediumAquamarine) , ("mediumblue", MediumBlue) , ("mediumorchid", MediumOrchid) , ("mediumpurple", MediumPurple) , ("mediumseagreen", MediumSeaGreen) , ("mediumslateblue", MediumSlateBlue) , ("mediumspringgreen", MediumSpringGreen) , ("mediumturquoise", MediumTurquoise) , ("mediumvioletred", MediumVioletRed) , ("midnightblue", MidnightBlue) , ("mintcream", MintCream) , ("mistyrose", MistyRose) , ("moccasin", Moccasin) , ("navajowhite", NavajoWhite) , ("navy", Navy) , ("oldlace", OldLace) , ("olive", Olive) , ("olivedrab", OliveDrab) , ("orange", Orange) , ("orangered", OrangeRed) , ("orchid", Orchid) , ("palegoldenrod", PaleGoldenrod) , ("palegreen", PaleGreen) , ("paleturquoise", PaleTurquoise) , ("palevioletred", PaleVioletRed) , ("papayawhip", PapayaWhip) , ("peachpuff", PeachPuff) , ("peru", Peru) , ("pink", Pink) , ("plum", Plum) , ("powderblue", PowderBlue) , ("purple", Purple) , ("red", Red) , ("rosybrown", RosyBrown) , ("royalblue", RoyalBlue) , ("saddlebrown", SaddleBrown) , ("salmon", Salmon) , ("sandybrown", SandyBrown) , ("seagreen", SeaGreen) , ("seashell", SeaShell) , ("sienna", Sienna) , ("silver", Silver) , ("skyblue", SkyBlue) , ("slateblue", SlateBlue) , ("slategray", SlateGray) , ("slategrey", SlateGray) , ("snow", Snow) , ("springgreen", SpringGreen) , ("steelblue", SteelBlue) , ("tan", Tan) , ("teal", Teal) , ("thistle", Thistle) , ("tomato", Tomato) , ("turquoise", Turquoise) , ("violet", Violet) , ("wheat", Wheat) , ("white", White) , ("whitesmoke", WhiteSmoke) , ("yellow", Yellow) , ("yellowgreen", YellowGreen) ] -- | Convert an 'SVGColor' to its equivalent 'Colour' value. svgColour :: SVGColor -> Colour Double svgColour AliceBlue = sRGB24 240 248 255 svgColour AntiqueWhite = sRGB24 250 235 215 svgColour Aqua = sRGB24 0 255 255 svgColour Aquamarine = sRGB24 127 255 212 svgColour Azure = sRGB24 240 255 255 svgColour Beige = sRGB24 245 245 220 svgColour Bisque = sRGB24 255 228 196 svgColour Black = sRGB24 0 0 0 svgColour BlanchedAlmond = sRGB24 255 235 205 svgColour Blue = sRGB24 0 0 255 svgColour BlueViolet = sRGB24 138 43 226 svgColour Brown = sRGB24 165 42 42 svgColour Burlywood = sRGB24 222 184 135 svgColour CadetBlue = sRGB24 95 158 160 svgColour Chartreuse = sRGB24 127 255 0 svgColour Chocolate = sRGB24 210 105 30 svgColour Coral = sRGB24 255 127 80 svgColour CornflowerBlue = sRGB24 100 149 237 svgColour Cornsilk = sRGB24 255 248 220 svgColour Crimson = sRGB24 220 20 60 svgColour Cyan = sRGB24 0 255 255 svgColour DarkBlue = sRGB24 0 0 139 svgColour DarkCyan = sRGB24 0 139 139 svgColour DarkGoldenrod = sRGB24 184 134 11 svgColour DarkGray = sRGB24 169 169 169 svgColour DarkGreen = sRGB24 0 100 0 svgColour DarkKhaki = sRGB24 189 183 107 svgColour DarkMagenta = sRGB24 139 0 139 svgColour DarkOliveGreen = sRGB24 85 107 47 svgColour DarkOrange = sRGB24 255 140 0 svgColour DarkOrchid = sRGB24 153 50 204 svgColour DarkRed = sRGB24 139 0 0 svgColour DarkSalmon = sRGB24 233 150 122 svgColour DarkSeaGreen = sRGB24 143 188 143 svgColour DarkSlateBlue = sRGB24 72 61 139 svgColour DarkSlateGray = sRGB24 47 79 79 svgColour DarkTurquoise = sRGB24 0 206 209 svgColour DarkViolet = sRGB24 148 0 211 svgColour DeepPink = sRGB24 255 20 147 svgColour DeepSkyBlue = sRGB24 0 191 255 svgColour DimGray = sRGB24 105 105 105 svgColour DodgerBlue = sRGB24 30 144 255 svgColour Firebrick = sRGB24 178 34 34 svgColour FloralWhite = sRGB24 255 250 240 svgColour ForestGreen = sRGB24 34 139 34 svgColour Fuchsia = sRGB24 255 0 255 svgColour Gainsboro = sRGB24 220 220 220 svgColour GhostWhite = sRGB24 248 248 255 svgColour Gold = sRGB24 255 215 0 svgColour Goldenrod = sRGB24 218 165 32 svgColour Gray = sRGB24 128 128 128 svgColour Green = sRGB24 0 128 0 svgColour GreenYellow = sRGB24 173 255 47 svgColour Honeydew = sRGB24 240 255 240 svgColour HotPink = sRGB24 255 105 180 svgColour IndianRed = sRGB24 205 92 92 svgColour Indigo = sRGB24 75 0 130 svgColour Ivory = sRGB24 255 255 240 svgColour Khaki = sRGB24 240 230 140 svgColour Lavender = sRGB24 230 230 250 svgColour LavenderBlush = sRGB24 255 240 245 svgColour LawnGreen = sRGB24 124 252 0 svgColour LemonChiffon = sRGB24 255 250 205 svgColour LightBlue = sRGB24 173 216 230 svgColour LightCoral = sRGB24 240 128 128 svgColour LightCyan = sRGB24 224 255 255 svgColour LightGoldenrodYellow = sRGB24 250 250 210 svgColour LightGray = sRGB24 211 211 211 svgColour LightGreen = sRGB24 144 238 144 svgColour LightPink = sRGB24 255 182 193 svgColour LightSalmon = sRGB24 255 160 122 svgColour LightSeaGreen = sRGB24 32 178 170 svgColour LightSkyBlue = sRGB24 135 206 250 svgColour LightSlateGray = sRGB24 119 136 153 svgColour LightSteelBlue = sRGB24 176 196 222 svgColour LightYellow = sRGB24 255 255 224 svgColour Lime = sRGB24 0 255 0 svgColour LimeGreen = sRGB24 50 205 50 svgColour Linen = sRGB24 250 240 230 svgColour Magenta = sRGB24 255 0 255 svgColour Maroon = sRGB24 128 0 0 svgColour MediumAquamarine = sRGB24 102 205 170 svgColour MediumBlue = sRGB24 0 0 205 svgColour MediumOrchid = sRGB24 186 85 211 svgColour MediumPurple = sRGB24 147 112 219 svgColour MediumSeaGreen = sRGB24 60 179 113 svgColour MediumSlateBlue = sRGB24 123 104 238 svgColour MediumSpringGreen = sRGB24 0 250 154 svgColour MediumTurquoise = sRGB24 72 209 204 svgColour MediumVioletRed = sRGB24 199 21 133 svgColour MidnightBlue = sRGB24 25 25 112 svgColour MintCream = sRGB24 245 255 250 svgColour MistyRose = sRGB24 255 228 225 svgColour Moccasin = sRGB24 255 228 181 svgColour NavajoWhite = sRGB24 255 222 173 svgColour Navy = sRGB24 0 0 128 svgColour OldLace = sRGB24 253 245 230 svgColour Olive = sRGB24 128 128 0 svgColour OliveDrab = sRGB24 107 142 35 svgColour Orange = sRGB24 255 165 0 svgColour OrangeRed = sRGB24 255 69 0 svgColour Orchid = sRGB24 218 112 214 svgColour PaleGoldenrod = sRGB24 238 232 170 svgColour PaleGreen = sRGB24 152 251 152 svgColour PaleTurquoise = sRGB24 175 238 238 svgColour PaleVioletRed = sRGB24 219 112 147 svgColour PapayaWhip = sRGB24 255 239 213 svgColour PeachPuff = sRGB24 255 218 185 svgColour Peru = sRGB24 205 133 63 svgColour Pink = sRGB24 255 192 203 svgColour Plum = sRGB24 221 160 221 svgColour PowderBlue = sRGB24 176 224 230 svgColour Purple = sRGB24 128 0 128 svgColour Red = sRGB24 255 0 0 svgColour RosyBrown = sRGB24 188 143 143 svgColour RoyalBlue = sRGB24 65 105 225 svgColour SaddleBrown = sRGB24 139 69 19 svgColour Salmon = sRGB24 250 128 114 svgColour SandyBrown = sRGB24 244 164 96 svgColour SeaGreen = sRGB24 46 139 87 svgColour SeaShell = sRGB24 255 245 238 svgColour Sienna = sRGB24 160 82 45 svgColour Silver = sRGB24 192 192 192 svgColour SkyBlue = sRGB24 135 206 235 svgColour SlateBlue = sRGB24 106 90 205 svgColour SlateGray = sRGB24 112 128 144 svgColour Snow = sRGB24 255 250 250 svgColour SpringGreen = sRGB24 0 255 127 svgColour SteelBlue = sRGB24 70 130 180 svgColour Tan = sRGB24 210 180 140 svgColour Teal = sRGB24 0 128 128 svgColour Thistle = sRGB24 216 191 216 svgColour Tomato = sRGB24 255 99 71 svgColour Turquoise = sRGB24 64 224 208 svgColour Violet = sRGB24 238 130 238 svgColour Wheat = sRGB24 245 222 179 svgColour White = sRGB24 255 255 255 svgColour WhiteSmoke = sRGB24 245 245 245 svgColour Yellow = sRGB24 255 255 0 svgColour YellowGreen = sRGB24 154 205 50 graphviz-2999.20.2.0/Data/GraphViz/Attributes/HTML.hs0000644000000000000000000006770114535166704020105 0ustar0000000000000000{-# LANGUAGE CPP, OverloadedStrings, PatternGuards #-} {- | Module : Data.GraphViz.Attributes.HTML Description : Specification of HTML-like types for Graphviz. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module is written to be imported qualified. It defines the syntax for HTML-like values for use in Graphviz. Please note that these values are /not/ really HTML, but the term \"HTML\" is used throughout as it is less cumbersome than \"HTML-like\". To be able to use this, the version of Graphviz must be at least 1.10. For more information, please see: The actual definition of the syntax specifies that these types must be valid XML syntax. As such, this assumed when printing and parsing, though the correct escape/descaping for @\"@, @&@, @\<@ and @\>@ are automatically done when printing and parsing. Differences from how Graphviz treats HTML-like values: * Graphviz only specifies the above-listed characters must be escaped; however, internally it also escapes @-@, @\'@ and multiple sequences of spaces. This library attempts to match this behaviour. Please let me know if this behaviour (especially about escaping multiple spaces) is unwanted. * When parsing escaped HTML characters, numeric escapes are converted to the corresponding character as are the various characters listed above; all other escaped characters (apart from those listed above) are silently ignored and removed from the input (since technically these must be valid /XML/, which doesn't recognise as many named escape characters as does HTML). * All whitespace read in is kept (even if Graphviz would ignore multiple whitespace characters); when printing them, however, they are replaced with non-breaking spaces. As such, if multiple literal whitespace characters are used in a sequence, then the result of parsing and then printing some Dot code will /not/ be the same as the initial Dot code. Furthermore, all whitespace characters are printed as spaces. * It is assumed that all parsed @&@ values are the beginning of an XML escape sequence (which /must/ finish with a @;@ character). * There should be no pre-escaped characters in values; when printing, the @&@ will get escaped without considering if that is an escaped character. -} module Data.GraphViz.Attributes.HTML ( Label(..) , Text , TextItem(..) , Format(..) , Table(..) , Row(..) , Cell(..) , Img(..) , Attributes , Attribute(..) , Align(..) , VAlign(..) , CellFormat(..) , Scale(..) , Side(..) , Style(..) ) where import Data.GraphViz.Attributes.Colors import Data.GraphViz.Attributes.Internal import Data.GraphViz.Internal.Util (bool) import Data.GraphViz.Parsing import Data.GraphViz.Printing import Data.Char (chr, isSpace, ord) import Data.Function (on) import Data.List (delete) import qualified Data.Map as Map import Data.Maybe (catMaybes, listToMaybe) import qualified Data.Text.Lazy as T import Data.Word (Word16, Word8) import Numeric (readHex) #if !MIN_VERSION_base (4,13,0) import Data.Monoid ((<>)) #endif -- ----------------------------------------------------------------------------- -- | The overall type for HTML-like labels. Fundamentally, HTML-like -- values in Graphviz are either textual (i.e. a single element with -- formatting) or a table. Note that 'Label' values can be -- nested via 'LabelCell'. data Label = Text Text | Table Table deriving (Eq, Ord, Show, Read) instance PrintDot Label where unqtDot (Text txt) = unqtDot txt unqtDot (Table tbl) = unqtDot tbl instance ParseDot Label where -- Try parsing Table first in case of a FONT tag being used. parseUnqt = fmap Table parseUnqt `onFail` fmap Text parseUnqt `adjustErr` ("Can't parse Html.Label\n\t"++) parse = parseUnqt -- | Represents a textual component of an HTML-like label. It is -- assumed that a 'Text' list is non-empty. It is preferable -- to \"group\" 'Str' values together rather than have -- individual ones. Note that when printing, the individual values -- are concatenated together without spaces, and when parsing -- anything that isn't a tag is assumed to be a 'Str': that is, -- something like \"@\ \@\" is parsed as: -- -- > [Newline [], Str " ", Newline []] type Text = [TextItem] -- | Textual items in HTML-like labels. data TextItem = Str T.Text -- | Only accepts an optional 'Align' -- 'Attribute'; defined this way for ease of -- printing/parsing. | Newline Attributes | Font Attributes Text -- | Only available in Graphviz >= 2.28.0. | Format Format Text deriving (Eq, Ord, Show, Read) instance PrintDot TextItem where unqtDot (Str str) = escapeValue str unqtDot (Newline as) = printEmptyTag (text "BR") as unqtDot (Font as txt) = printFontTag as $ unqtDot txt unqtDot (Format fmt txt) = printTag (unqtDot fmt) [] $ unqtDot txt unqtListToDot = hcat . mapM unqtDot listToDot = unqtListToDot instance ParseDot TextItem where parseUnqt = oneOf [ fmap Str unescapeValue , parseEmptyTag Newline "BR" , parseFontTag Font parseUnqt , parseTagRep Format parseUnqt parseUnqt ] `adjustErr` ("Can't parse Html.TextItem\n\t"++) parse = parseUnqt parseUnqtList = many parseUnqt parseList = parseUnqtList data Format = Italics | Bold | Underline | Overline -- ^ Requires Graphviz >= 2.38.0. | Subscript | Superscript deriving (Eq, Ord, Bounded, Enum, Show, Read) instance PrintDot Format where unqtDot Italics = text "I" unqtDot Bold = text "B" unqtDot Underline = text "U" unqtDot Overline = text "O" unqtDot Subscript = text "SUB" unqtDot Superscript = text "SUP" instance ParseDot Format where parseUnqt = stringValue [ ("I", Italics) , ("B", Bold) , ("U", Underline) , ("O", Overline) , ("SUB", Subscript) , ("SUP", Superscript) ] -- | A table in HTML-like labels. Tables are optionally wrapped in -- overall @FONT@ tags. data Table = HTable { -- | Optional @FONT@ attributes. @'Just' -- []@ denotes empty @FONT@ tags; -- @'Nothing'@ denotes no such tags. tableFontAttrs :: Maybe Attributes , tableAttrs :: Attributes -- | This list is assumed to be non-empty. , tableRows :: [Row] } deriving (Eq, Ord, Show, Read) instance PrintDot Table where unqtDot tbl = case tableFontAttrs tbl of (Just as) -> printFontTag as tbl' Nothing -> tbl' where tbl' = printTag (text "TABLE") (tableAttrs tbl) (toDot $ tableRows tbl) instance ParseDot Table where parseUnqt = wrapWhitespace (parseFontTag addFontAttrs pTbl) `onFail` pTbl `adjustErr` ("Can't parse Html.Table\n\t"++) where pTbl = wrapWhitespace $ parseTag (HTable Nothing) "TABLE" (wrapWhitespace parseUnqt) addFontAttrs fas tbl = tbl { tableFontAttrs = Just fas } parse = parseUnqt -- | A row in a 'Table'. The list of 'Cell' values is -- assumed to be non-empty. data Row = Cells [Cell] | HorizontalRule -- ^ Should be between 'Cells' values, -- requires Graphviz >= 2.29.0 deriving (Eq, Ord, Show, Read) instance PrintDot Row where unqtDot (Cells cs) = printTag (text "TR") [] $ unqtDot cs unqtDot HorizontalRule = printEmptyTag (text "HR") [] unqtListToDot = align . cat . mapM unqtDot listToDot = unqtListToDot instance ParseDot Row where -- To save doing it manually, use 'parseTag' and ignore any -- 'Attributes' that it might accidentally parse. parseUnqt = wrapWhitespace $ parseTag (const Cells) "TR" parseUnqt `onFail` parseEmptyTag (const HorizontalRule) "HR" `adjustErr` ("Can't parse Html.Row\n\t"++) parse = parseUnqt parseUnqtList = wrapWhitespace $ sepBy1 parseUnqt whitespace parseList = parseUnqtList -- | Cells either recursively contain another 'Label' or else a -- path to an image file. data Cell = LabelCell Attributes Label | ImgCell Attributes Img | VerticalRule -- ^ Should be between 'LabelCell' or -- 'ImgCell' values, requires Graphviz >= -- 2.29.0 deriving (Eq, Ord, Show, Read) instance PrintDot Cell where unqtDot (LabelCell as l) = printCell as $ unqtDot l unqtDot (ImgCell as img) = printCell as $ unqtDot img unqtDot VerticalRule = printEmptyTag (text "VR") [] unqtListToDot = hsep . mapM unqtDot listToDot = unqtListToDot printCell :: Attributes -> DotCode -> DotCode printCell = printTag (text "TD") instance ParseDot Cell where parseUnqt = oneOf [ parseCell LabelCell parse , parseCell ImgCell $ wrapWhitespace parse , parseEmptyTag (const VerticalRule) "VR" ] `adjustErr` ("Can't parse Html.Cell\n\t"++) where parseCell = (`parseTag` "TD") parse = parseUnqt parseUnqtList = wrapWhitespace $ sepBy1 parseUnqt whitespace parseList = parseUnqtList -- | The path to an image; accepted 'Attributes' are 'Scale' and 'Src'. newtype Img = Img Attributes deriving (Eq, Ord, Show, Read) instance PrintDot Img where unqtDot (Img as) = printEmptyTag (text "IMG") as instance ParseDot Img where parseUnqt = wrapWhitespace (parseEmptyTag Img "IMG") `adjustErr` ("Can't parse Html.Img\n\t"++) parse = parseUnqt -- ----------------------------------------------------------------------------- -- | The various HTML-like label-specific attributes being used. type Attributes = [Attribute] -- | Note that not all 'Attribute' values are valid everywhere: -- see the comments for each one on where it is valid. data Attribute = Align Align -- ^ Valid for: 'Table', 'Cell', 'Newline'. | BAlign Align -- ^ Valid for: 'Cell'. | BGColor Color -- ^ Valid for: 'Table' (including 'tableFontAttrs'), 'Cell', 'Font'. | Border Word8 -- ^ Valid for: 'Table', 'Cell'. Default is @1@; @0@ represents no border. | CellBorder Word8 -- ^ Valid for: 'Table'. Default is @1@; @0@ represents no border. | CellPadding Word8 -- ^ Valid for: 'Table', 'Cell'. Default is @2@. | CellSpacing Word8 -- ^ Valid for: 'Table', 'Cell'. Default is @2@; maximum is @127@. | Color Color -- ^ Valid for: 'Table', 'Cell'. | ColSpan Word16 -- ^ Valid for: 'Cell'. Default is @1@. | Columns CellFormat -- ^ Valid for: 'Table'. Requires Graphviz >= 2.40.1 | Face T.Text -- ^ Valid for: 'tableFontAttrs', 'Font'. | FixedSize Bool -- ^ Valid for: 'Table', 'Cell'. Default is @'False'@. | GradientAngle Int -- ^ Valid for: 'Table', 'Cell'. Default is @0@. Requires Graphviz >= 2.40.1 | Height Word16 -- ^ Valid for: 'Table', 'Cell'. | HRef T.Text -- ^ Valid for: 'Table', 'Cell'. | ID T.Text -- ^ Valid for: 'Table', 'Cell'. Requires Graphviz >= 2.29.0 | PointSize Double -- ^ Valid for: 'tableFontAttrs', 'Font'. | Port PortName -- ^ Valid for: 'Table', 'Cell'. | Rows CellFormat -- ^ Valid for: 'Table'. Requires Graphviz >= 2.40.1 | RowSpan Word16 -- ^ Valid for: 'Cell'. | Scale Scale -- ^ Valid for: 'Img'. | Sides [Side] -- ^ Valid for: 'Table', 'Cell'. Default is @['LeftSide', 'TopSide', 'RightSide', 'BottomSide']@. Requires Graphviz >= 2.40.1 | Src FilePath -- ^ Valid for: 'Img'. | Style Style -- ^ Valid for: 'Table', 'Cell'. Requires Graphviz >= 2.40.1 | Target T.Text -- ^ Valid for: 'Table', 'Cell'. | Title T.Text -- ^ Valid for: 'Table', 'Cell'. Has an alias of @TOOLTIP@. | VAlign VAlign -- ^ Valid for: 'Table', 'Cell'. | Width Word16 -- ^ Valid for: 'Table', 'Cell'. deriving (Eq, Ord, Show, Read) instance PrintDot Attribute where unqtDot (Align v) = printHtmlField "ALIGN" v unqtDot (BAlign v) = printHtmlField "BALIGN" v unqtDot (BGColor v) = printHtmlField "BGCOLOR" v unqtDot (Border v) = printHtmlField "BORDER" v unqtDot (CellBorder v) = printHtmlField "CELLBORDER" v unqtDot (CellPadding v) = printHtmlField "CELLPADDING" v unqtDot (CellSpacing v) = printHtmlField "CELLSPACING" v unqtDot (Color v) = printHtmlField "COLOR" v unqtDot (ColSpan v) = printHtmlField "COLSPAN" v unqtDot (Columns v) = printHtmlField "COLUMNS" v unqtDot (Face v) = printHtmlField' "FACE" $ escapeAttribute v unqtDot (FixedSize v) = printHtmlField' "FIXEDSIZE" $ printBoolHtml v unqtDot (GradientAngle v) = printHtmlField "GRADIENTANGLE" v unqtDot (Height v) = printHtmlField "HEIGHT" v unqtDot (HRef v) = printHtmlField' "HREF" $ escapeAttribute v unqtDot (ID v) = printHtmlField' "ID" $ escapeAttribute v unqtDot (PointSize v) = printHtmlField "POINT-SIZE" v unqtDot (Port v) = printHtmlField' "PORT" . escapeAttribute $ portName v unqtDot (Rows v) = printHtmlField "ROWS" v unqtDot (RowSpan v) = printHtmlField "ROWSPAN" v unqtDot (Scale v) = printHtmlField "SCALE" v unqtDot (Sides v) = printHtmlField "SIDES" v unqtDot (Src v) = printHtmlField' "SRC" . escapeAttribute $ T.pack v unqtDot (Style v) = printHtmlField "STYLE" v unqtDot (Target v) = printHtmlField' "TARGET" $ escapeAttribute v unqtDot (Title v) = printHtmlField' "TITLE" $ escapeAttribute v unqtDot (VAlign v) = printHtmlField "VALIGN" v unqtDot (Width v) = printHtmlField "WIDTH" v unqtListToDot = hsep . mapM unqtDot listToDot = unqtListToDot -- | Only to be used when the 'PrintDot' instance of @a@ matches the -- HTML syntax (i.e. numbers and @Html.*@ values; 'Color' values also -- seem to work). printHtmlField :: (PrintDot a) => T.Text -> a -> DotCode printHtmlField f = printHtmlField' f . unqtDot printHtmlField' :: T.Text -> DotCode -> DotCode printHtmlField' f v = text f <> equals <> dquotes v instance ParseDot Attribute where parseUnqt = oneOf [ parseHtmlField Align "ALIGN" , parseHtmlField BAlign "BALIGN" , parseHtmlField BGColor "BGCOLOR" , parseHtmlField Border "BORDER" , parseHtmlField CellBorder "CELLBORDER" , parseHtmlField CellPadding "CELLPADDING" , parseHtmlField CellSpacing "CELLSPACING" , parseHtmlField Color "COLOR" , parseHtmlField ColSpan "COLSPAN" , parseHtmlField Columns "COLUMNS" , parseHtmlField' Face "FACE" unescapeAttribute , parseHtmlField' FixedSize "FIXEDSIZE" parseBoolHtml , parseHtmlField GradientAngle "GRADIENTANGLE" , parseHtmlField Height "HEIGHT" , parseHtmlField' HRef "HREF" unescapeAttribute , parseHtmlField' ID "ID" unescapeAttribute , parseHtmlField PointSize "POINT-SIZE" , parseHtmlField' (Port . PN) "PORT" unescapeAttribute , parseHtmlField Rows "ROWS" , parseHtmlField RowSpan "ROWSPAN" , parseHtmlField Scale "SCALE" , parseHtmlField Sides "SIDES" , parseHtmlField' Src "SRC" $ fmap T.unpack unescapeAttribute , parseHtmlField Style "STYLE" , parseHtmlField' Target "TARGET" unescapeAttribute , parseHtmlField' Title "TITLE" unescapeAttribute `onFail` parseHtmlField' Title "TOOLTIP" unescapeAttribute , parseHtmlField VAlign "VALIGN" , parseHtmlField Width "WIDTH" ] parse = parseUnqt parseUnqtList = sepBy parseUnqt whitespace1 -- needs at least one whitespace char parseList = parseUnqtList parseHtmlField :: (ParseDot a) => (a -> Attribute) -> String -> Parse Attribute parseHtmlField c f = parseHtmlField' c f parseUnqt parseHtmlField' :: (a -> Attribute) -> String -> Parse a -> Parse Attribute parseHtmlField' c f p = string f *> parseEq *> ( c <$> ( quotedParse p `adjustErr` (("Can't parse HTML.Attribute." ++ f ++ "\n\t")++) ) ) -- Can't use liftEqParse, etc. here because it causes backtracking -- problems when the attributes could apply to multiple constructors. -- This includes using commit! (Example: if it starts with a FONT tag, -- is it a Table or Text? -- | Specifies horizontal placement. When an object is allocated more -- space than required, this value determines where the extra space -- is placed left and right of the object. data Align = HLeft | HCenter -- ^ Default value. | HRight | HText -- ^ 'LabelCell' values only; aligns lines of text -- using the full cell width. The alignment of a -- line is determined by its (possibly implicit) -- associated 'Newline' element. deriving (Eq, Ord, Bounded, Enum, Show, Read) instance PrintDot Align where unqtDot HLeft = text "LEFT" unqtDot HCenter = text "CENTER" unqtDot HRight = text "RIGHT" unqtDot HText = text "TEXT" instance ParseDot Align where parseUnqt = oneOf [ stringRep HLeft "LEFT" , stringRep HCenter "CENTER" , stringRep HRight "RIGHT" , stringRep HText "TEXT" ] parse = parseUnqt -- | Specifies vertical placement. When an object is allocated more -- space than required, this value determines where the extra space -- is placed above and below the object. data VAlign = HTop | HMiddle -- ^ Default value. | HBottom deriving (Eq, Ord, Bounded, Enum, Show, Read) instance PrintDot VAlign where unqtDot HTop = text "TOP" unqtDot HMiddle = text "MIDDLE" unqtDot HBottom = text "BOTTOM" instance ParseDot VAlign where parseUnqt = oneOf [ stringRep HTop "TOP" , stringRep HMiddle "MIDDLE" , stringRep HBottom "BOTTOM" ] parse = parseUnqt data CellFormat = RuleBetween deriving (Eq, Ord, Bounded, Enum, Show, Read) instance PrintDot CellFormat where unqtDot RuleBetween = text "*" instance ParseDot CellFormat where parseUnqt = stringRep RuleBetween "*" parse = parseUnqt -- | Specifies how an image will use any extra space available in its -- cell. If undefined, the image inherits the value of the -- @ImageScale@ attribute. data Scale = NaturalSize -- ^ Default value. | ScaleUniformly | ExpandWidth | ExpandHeight | ExpandBoth deriving (Eq, Ord, Bounded, Enum, Show, Read) instance PrintDot Scale where unqtDot NaturalSize = text "FALSE" unqtDot ScaleUniformly = text "TRUE" unqtDot ExpandWidth = text "WIDTH" unqtDot ExpandHeight = text "HEIGHT" unqtDot ExpandBoth = text "BOTH" instance ParseDot Scale where parseUnqt = oneOf [ stringRep NaturalSize "FALSE" , stringRep ScaleUniformly "TRUE" , stringRep ExpandWidth "WIDTH" , stringRep ExpandHeight "HEIGHT" , stringRep ExpandBoth "BOTH" ] parse = parseUnqt -- | Which sides of a border in a cell or table should be drawn, if a -- border is drawn. data Side = LeftSide | RightSide | TopSide | BottomSide deriving (Eq, Ord, Bounded, Enum, Show, Read) instance PrintDot Side where unqtDot LeftSide = text "L" unqtDot RightSide = text "R" unqtDot TopSide = text "T" unqtDot BottomSide = text "B" unqtListToDot = hcat . mapM unqtDot listToDot = unqtListToDot instance ParseDot Side where parseUnqt = oneOf [ stringRep LeftSide "L" , stringRep RightSide "R" , stringRep TopSide "T" , stringRep BottomSide "B" ] parse = parseUnqt parseUnqtList = many parseUnqt parseList = parseUnqtList data Style = Rounded -- ^ Valid for 'Table' | Radial -- ^ Valid for 'Table', 'Cell'. deriving (Eq, Ord, Bounded, Enum, Show, Read) instance PrintDot Style where unqtDot Rounded = text "ROUNDED" unqtDot Radial = text "RADIAL" instance ParseDot Style where parseUnqt = oneOf [ stringRep Rounded "ROUNDED" , stringRep Radial "RADIAL" ] parse = parseUnqt -- ----------------------------------------------------------------------------- escapeAttribute :: T.Text -> DotCode escapeAttribute = escapeHtml False escapeValue :: T.Text -> DotCode escapeValue = escapeHtml True escapeHtml :: Bool -> T.Text -> DotCode escapeHtml quotesAllowed = hcat . fmap concat . mapM (escapeSegment . T.unpack) . T.groupBy ((==) `on` isSpace) where -- Note: use numeric version of space rather than nbsp, since this -- matches what Graphviz does (since Inkscape apparently can't -- cope with nbsp). escapeSegment (s:sps) | isSpace s = liftA2 (:) (char s) $ mapM numEscape sps escapeSegment txt = mapM xmlChar txt allowQuotes = if quotesAllowed then Map.delete '"' else id escs = allowQuotes $ Map.fromList htmlEscapes xmlChar c = maybe (char c) escape $ c `Map.lookup` escs numEscape = escape' . (<>) (char '#') . int . ord escape' e = char '&' <> e <> char ';' escape = escape' . text unescapeAttribute :: Parse T.Text unescapeAttribute = unescapeHtml False unescapeValue :: Parse T.Text unescapeValue = unescapeHtml True -- | Parses an HTML-compatible 'String', de-escaping known characters. -- Note: this /will/ fail if an unknown non-numeric HTML-escape is -- used. unescapeHtml :: Bool -> Parse T.Text unescapeHtml quotesAllowed = fmap (T.pack . catMaybes) . many1 . oneOf $ [ parseEscpd , validChars ] where parseEscpd :: Parse (Maybe Char) parseEscpd = do character '&' esc <- many1Satisfy (';' /=) character ';' let c = case T.uncons $ T.toLower esc of Just ('#',dec) | Just ('x',hex) <- T.uncons dec -> readMaybe readHex $ T.unpack hex | otherwise -> readMaybe readInt $ T.unpack dec _ -> esc `Map.lookup` escMap return c readMaybe f str = do (n, []) <- listToMaybe $ f str return $ chr n readInt :: ReadS Int readInt = reads allowQuotes = if quotesAllowed then delete '"' else id escMap = Map.fromList htmlUnescapes validChars = fmap Just $ satisfy (`notElem` needEscaping) needEscaping = allowQuotes $ map fst htmlEscapes -- | The characters that need to be escaped and what they need to be -- replaced with (sans @'&'@). htmlEscapes :: [(Char, T.Text)] htmlEscapes = [ ('"', "quot") , ('<', "lt") , ('>', "gt") , ('&', "amp") ] -- | Flip the order and add extra values that might be escaped. More -- specifically, provide the escape code for spaces (@\"nbsp\"@) and -- apostrophes (@\"apos\"@) since they aren't used for escaping. htmlUnescapes :: [(T.Text, Char)] htmlUnescapes = maybeEscaped ++ map (uncurry $ flip (,)) htmlEscapes where maybeEscaped = [("nbsp", ' '), ("apos", '\'')] printBoolHtml :: Bool -> DotCode printBoolHtml = text . bool "FALSE" "TRUE" parseBoolHtml :: Parse Bool parseBoolHtml = stringRep True "TRUE" `onFail` stringRep False "FALSE" -- ----------------------------------------------------------------------------- -- | Print something like @value<\/FOO>@ printTag :: DotCode -> Attributes -> DotCode -> DotCode printTag t as v = angled (t <+> toDot as) <> v <> angled (fslash <> t) printFontTag :: Attributes -> DotCode -> DotCode printFontTag = printTag (text "FONT") -- | Print something like @@ printEmptyTag :: DotCode -> Attributes -> DotCode printEmptyTag t as = angled $ t <+> toDot as <> fslash -- ----------------------------------------------------------------------------- -- Note: can't use bracket here because we're not completely -- discarding everything from the opening bracket. -- Not using parseTagRep for parseTag because open/close case -- is different; worth fixing? -- | Parse something like @value<\/FOO>@ parseTag :: (Attributes -> val -> tag) -> String -> Parse val -> Parse tag parseTag c t pv = c <$> parseAngled openingTag <*> wrapWhitespace pv <* parseAngled (character '/' *> t' *> whitespace) `adjustErr` (("Can't parse Html tag: " ++ t ++ "\n\t")++) where t' = string t openingTag :: Parse Attributes openingTag = t' *> tryParseList' (whitespace1 >> parse) <* whitespace parseFontTag :: (Attributes -> val -> tag) -> Parse val -> Parse tag parseFontTag = (`parseTag` "FONT") -- Should this just be specialised for tagName ~ Format ? -- | Parse something like @value<\/FOO>@. parseTagRep :: (tagName -> val -> tag) -> Parse tagName -> Parse val -> Parse tag parseTagRep c pt pv = c <$> parseAngled (pt `discard` whitespace) <*> pv <* parseAngled (character '/' *> pt *> whitespace) `adjustErr` ("Can't parse attribute-less Html tag\n\t"++) -- | Parse something like @@ parseEmptyTag :: (Attributes -> tag) -> String -> Parse tag parseEmptyTag c t = c <$> parseAngled ( string t *> tryParseList' (whitespace1 *> parse) <* whitespace <* character '/' ) `adjustErr` (("Can't parse empty Html tag: " ++ t ++ "\n\t")++) graphviz-2999.20.2.0/Data/GraphViz/PreProcessing.hs0000644000000000000000000001202014535166704017756 0ustar0000000000000000{-# LANGUAGE CPP #-} {- | Module : Data.GraphViz.PreProcessing Description : Pre-process imported Dot code. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com \"Real life\" Dot code contains various items that are not directly parseable by this library. This module defines the 'preProcess' function to remove these components, which include: * Comments (both @\/\* ... *\/@ style and @\/\/ ... @ style); * Pre-processor lines (lines starting with a @#@); * Split lines (by inserting a @\\@ the rest of that \"line\" is continued on the next line). * Strings concatenated together using @\"...\" + \"...\"@; these are concatenated into one big string. -} module Data.GraphViz.PreProcessing(preProcess) where import Data.GraphViz.Exception (GraphvizException (NotDotCode), throw) import Data.GraphViz.Parsing import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T import Data.Text.Lazy.Builder (Builder) import qualified Data.Text.Lazy.Builder as B #if !(MIN_VERSION_base(4,8,0)) import Data.Monoid (Monoid (..), mconcat) #endif -- ----------------------------------------------------------------------------- -- Filtering out unwanted Dot items such as comments -- | Remove unparseable features of Dot, such as comments and -- multi-line strings (which are converted to single-line strings). preProcess :: Text -> Text preProcess t = case fst $ runParser parseOutUnwanted t of (Right r) -> B.toLazyText r (Left l) -> throw (NotDotCode l) -- snd should be null -- | Parse out comments and make quoted strings spread over multiple -- lines only over a single line. Should parse the /entire/ input -- 'Text'. parseOutUnwanted :: Parse Builder parseOutUnwanted = mconcat <$> many getNext where getNext = parseOK `onFail` parseConcatStrings `onFail` parseHTML `onFail` parseUnwanted `onFail` fmap B.singleton next parseOK = B.fromLazyText <$> many1Satisfy (`notElem` ['\n', '\r', '\\', '/', '"', '<']) -- | Parses an unwanted part of the Dot code (comments and -- pre-processor lines; also un-splits lines). parseUnwanted :: (Monoid m) => Parse m parseUnwanted = oneOf [ parseLineComment , parseMultiLineComment , parsePreProcessor , parseSplitLine ] -- | Remove pre-processor lines (that is, those that start with a -- @#@). Will consume the newline from the beginning of the -- previous line, but will leave the one from the pre-processor line -- there (so in the end it just removes the line). parsePreProcessor :: (Monoid m) => Parse m parsePreProcessor = newline *> character '#' *> consumeLine *> pure mempty -- | Parse @//@-style comments. parseLineComment :: (Monoid m) => Parse m parseLineComment = string "//" -- Note: do /not/ consume the newlines, as they're -- needed in case the next line is a pre-processor -- line. *> consumeLine *> pure mempty -- | Parse @/* ... */@-style comments. parseMultiLineComment :: (Monoid m) => Parse m parseMultiLineComment = bracket start end (many inner) *> pure mempty where start = string "/*" end = string "*/" inner = (many1Satisfy ('*' /=) *> pure ()) `onFail` (character '*' *> satisfy ('/' /=) *> inner) parseConcatStrings :: Parse Builder parseConcatStrings = wrapQuotes . mconcat <$> sepBy1 parseString parseConcat where qParse = bracket (character '"') (commit $ character '"') parseString = qParse (mconcat <$> many parseInner) parseInner = (string "\\\"" *> pure (B.fromLazyText $ T.pack "\\\"")) `onFail` -- Need to parse an explicit `\', in case it ends the -- string (and thus the next step would get parsed by the -- previous option). (string "\\\\" *> pure (B.fromLazyText $ T.pack "\\\\")) `onFail` parseSplitLine -- in case there's a split mid-quote `onFail` fmap B.singleton (satisfy (quoteChar /=)) parseConcat = parseSep *> character '+' *> parseSep parseSep = many $ whitespace1 `onFail` parseUnwanted wrapQuotes str = qc `mappend` str `mappend` qc qc = B.singleton '"' -- | Lines can be split with a @\\@ at the end of the line. parseSplitLine :: (Monoid m) => Parse m parseSplitLine = character '\\' *> newline *> pure mempty parseHTML :: Parse Builder parseHTML = fmap (addAngled . mconcat) . parseAngled $ many inner where inner = parseHTML `onFail` (B.fromLazyText <$> many1Satisfy (\c -> c /= open && c /= close)) addAngled str = B.singleton open `mappend` str `mappend` B.singleton close open = '<' close = '>' graphviz-2999.20.2.0/Data/GraphViz/Exception.hs0000644000000000000000000000300614535166704017135 0ustar0000000000000000{-# LANGUAGE DeriveDataTypeable #-} {- | Module : Data.GraphViz.Exception Description : Graphviz-specific exceptions Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Exception ( GraphvizException(..) -- * Re-exported for convenience. , mapException , throw , throwIO , handle , bracket ) where import Control.Exception import Data.Typeable -- ----------------------------------------------------------------------------- -- | Exceptions that arise from using this library fall into four -- categories: -- -- * Unable to parse provided Dot code. -- -- * Dot code is not valid UTF-8. -- -- * An error when trying to run an external program (e.g. @dot@). -- -- * Treating a non-custom Attribute as a custom one. -- data GraphvizException = NotDotCode String | NotUTF8Dot String | GVProgramExc String | NotCustomAttr String deriving (Eq, Ord, Typeable) instance Show GraphvizException where showsPrec _ (NotDotCode str) = showString $ "Error when parsing Dot code:\n" ++ str showsPrec _ (NotUTF8Dot str) = showString $ "Invalid UTF-8 Dot code: " ++ str showsPrec _ (GVProgramExc str) = showString $ "Error running utility program: " ++ str showsPrec _ (NotCustomAttr str) = showString $ "Not a custom Attribute: " ++ str instance Exception GraphvizException graphviz-2999.20.2.0/Data/GraphViz/Algorithms.hs0000644000000000000000000004240514535166704017316 0ustar0000000000000000{-# LANGUAGE MonadComprehensions, MultiParamTypeClasses #-} {- | Module : Data.GraphViz.Algorithms Description : Various algorithms on Graphviz graphs. Copyright : (c) Matthew Sackman, Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com Defines various algorithms for use on 'DotRepr' graphs. These are typically re-implementations of behaviour found in existing Graphviz tools but without the I/O requirement. Note that one way that these algorithms differ from those found in Graphviz is that the order of clusters is /not/ maintained, which may affect layout in some cases. -} module Data.GraphViz.Algorithms ( -- * Canonicalisation Options -- $options CanonicaliseOptions(..) , defaultCanonOptions , dotLikeOptions -- * Canonicalisation -- $canonicalisation , canonicalise , canonicaliseOptions -- * Dealing with transitive edges -- $transitive , transitiveReduction , transitiveReductionOptions ) where import Data.GraphViz.Attributes.Complete (Attributes, defaultAttributeValue) import Data.GraphViz.Attributes.Same import Data.GraphViz.Internal.Util (bool) import Data.GraphViz.Types import Data.GraphViz.Types.Canonical import Data.GraphViz.Types.Internal.Common import Control.Arrow (first, second, (***)) import Control.Monad (unless) import Control.Monad.State (State, execState, gets, modify) import qualified Data.DList as DList import qualified Data.Foldable as F import Data.Function (on) import Data.List (deleteBy, groupBy, partition, sortBy, (\\)) import Data.Map (Map) import qualified Data.Map as Map import Data.Maybe (fromMaybe, listToMaybe, mapMaybe) import Data.Set (Set) import qualified Data.Set as Set -- ----------------------------------------------------------------------------- {- $options For simplicity, many algorithms end up using the canonicalisation functions to create the new 'DotGraph'. 'CanonicaliseOptions' allows you to configure how the output is generated. -} data CanonicaliseOptions = COpts { -- | Place edges in the clusters -- where their nodes are rather -- than in the top-level graph. edgesInClusters :: Bool -- | Put common 'Attributes' as -- top-level 'GlobalAttributes'. , groupAttributes :: Bool } deriving (Eq, Ord, Show, Read) defaultCanonOptions :: CanonicaliseOptions defaultCanonOptions = COpts { edgesInClusters = True , groupAttributes = True } -- | Options that are more like how @dot -Tcanon@ works. dotLikeOptions :: CanonicaliseOptions dotLikeOptions = COpts { edgesInClusters = True , groupAttributes = False } -- ----------------------------------------------------------------------------- {- $canonicalisation These functions implement similar functionality to @dot -Tcanon@ (i.e. creates a canonical form of any 'DotRepr' graph). without requiring IO. Note that due to implementation specifics the behaviour is not identical; in particular: * Any specified 'Attributes' that equal the defaults are stripped out (unless required to override a previous attribute that doesn't apply here). * Grouping of attributes (when @'groupAttributes = True'@) is much more conservative; only those node/edge attributes that are common to /all/ nodes and edges within that cluster (and within sub-clusters) are made global. * Sub-graphs aren't kept, only clusters. * 'ColorScheme' Attributes are removed (as all @Color@ values embed any needed color scheme anyway) as the output order of attributes may change (and this matters for the Haskell side of things). In particular, note that this function will create a single explicit definition for every node in the original graph and place it in the appropriate position in the cluster hierarchy. All edges are found in the deepest cluster that contains both nodes. -} -- | Canonicalise with some sensible defaults. canonicalise :: (DotRepr dg n) => dg n -> DotGraph n canonicalise = canonicaliseOptions defaultCanonOptions -- | As with 'canonicalise', but allow custom 'CanonicaliseOptions'. canonicaliseOptions :: (DotRepr dg n) => CanonicaliseOptions -> dg n -> DotGraph n canonicaliseOptions opts dg = cdg { strictGraph = graphIsStrict dg , directedGraph = graphIsDirected dg } where cdg = createCanonical opts (getID dg) gas cl nl es (gas, cl) = graphStructureInformationClean dg nl = nodeInformationClean True dg es = edgeInformationClean True dg type NodePath n = ([Maybe GraphID], DotNode n) type NodePaths n = [NodePath n] type EdgeClusters n = Map (Maybe GraphID) [DotEdge n] type EdgeLocations n = (EdgeClusters n, [DotEdge n]) data CanonControl n = CC { cOpts :: !CanonicaliseOptions , isGraph :: !Bool , clusters :: !ClusterLookup , clustEs :: !(EdgeLocations n) , topID :: !(Maybe GraphID) , topAttrs :: !Attributes } createCanonical :: (Ord n) => CanonicaliseOptions -> Maybe GraphID -> GlobalAttributes -> ClusterLookup -> NodeLookup n -> [DotEdge n] -> DotGraph n createCanonical opts gid gas cl nl es = promoteDSG $ makeGrouping cc ns where nUnlook (n,(p,as)) = (F.toList p, DotNode n as) -- DotNodes paired and sorted by their paths ns = sortBy (compLists `on` fst) . map nUnlook $ Map.toList nl es' = if edgesInClusters opts then edgeClusters nl es else (Map.empty, es) cc = CC { cOpts = opts , isGraph = True , clusters = cl , clustEs = es' , topID = gid , topAttrs = attrs gas } thisLevel :: NodePaths n -> (NodePaths n, [DotNode n]) thisLevel = second (map snd) . span (not . null . fst) makeGrouping :: CanonControl n -> NodePaths n -> DotSubGraph n makeGrouping cc cns = DotSG { isCluster = True , subGraphID = cID , subGraphStmts = stmts } where cID | isGraph cc = topID cc | otherwise = head . fst . head $ cns (nestedNs, ns) = thisLevel . bool (map $ first tail) id (isGraph cc) $ cns es = bool (fromMaybe [] . Map.lookup cID . fst) snd (isGraph cc) $ clustEs cc gas | isGraph cc = topAttrs cc | otherwise = attrs . snd $ clusters cc Map.! cID subGs = map (makeGrouping $ cc { isGraph = False }) . groupBy ((==) `on` (listToMaybe . fst)) $ nestedNs stmts = setGlobal (cOpts cc) gas $ DotStmts { attrStmts = [] , subGraphs = subGs , nodeStmts = ns , edgeStmts = es } setGlobal :: CanonicaliseOptions -> Attributes -- Specified cluster attributes -> DotStatements n -> DotStatements n setGlobal opts as stmts = stmts { attrStmts = globs' , subGraphs = sgs' , nodeStmts = ns' , edgeStmts = es' } where sgs = subGraphs stmts sStmts = map subGraphStmts sgs ns = nodeStmts stmts es = edgeStmts stmts sGlobs = map (partitionGlobal . attrStmts) sStmts (sgas,snas,seas) = unzip3 sGlobs gas' = as -- Can't change graph attrs! Need these! nas' = getCommonGlobs opts nodeStmts snas sStmts $ map nodeAttributes ns eas' = getCommonGlobs opts edgeStmts seas sStmts $ map edgeAttributes es globs' = nonEmptyGAs [ GraphAttrs gas' , NodeAttrs nas' , EdgeAttrs eas' ] ns' = map (\dn -> dn { nodeAttributes = nodeAttributes dn \\ nas' }) ns es' = map (\de -> de { edgeAttributes = edgeAttributes de \\ eas' }) es sgas' = updateGraphGlobs gas' sgas snas' = map (\\ nas') snas seas' = map (\\ eas') seas sGlobs' = zip3 sgas' snas' seas' sStmts' = zipWith (\ sSt sGl -> sSt { attrStmts = nonEmptyGAs $ unPartitionGlobal sGl }) sStmts sGlobs' sgs' = zipWith (\ sg sSt -> sg { subGraphStmts = sSt }) sgs sStmts' updateGraphGlobs :: Attributes -> [Attributes] -> [Attributes] updateGraphGlobs gas = map go where gasS = Set.fromList gas override = toSAttr $ nonSameDefaults gas -- * Remove any identical values -- * Override any different values go = Set.toList . (`Set.difference` gasS) -- Remove identical values . unSameSet . (`Set.union` override) -- Keeps existing values of constructors . toSAttr nonSameDefaults :: Attributes -> Attributes nonSameDefaults = mapMaybe (\ a -> [ a' | a' <- defaultAttributeValue a, a' /= a] ) getCommonGlobs :: CanonicaliseOptions -> (DotStatements n -> [a]) -> [Attributes] -- ^ From sub-graphs -> [DotStatements n] -- ^ Statements from the sub-graphs for testing. -> [Attributes] -- ^ From nodes/edges -> Attributes getCommonGlobs opts f sas stmts as | not $ groupAttributes opts = [] | otherwise = case sas' ++ as of [] -> [] [_] -> [] as' -> Set.toList . foldr1 Set.intersection $ map Set.fromList as' where sas' = keepIfAny f sas stmts -- Used to distinguish between having empty list of global attributes -- for nodes or edges because there aren't any nodes/edges, or because -- there aren't any common attributes keepIfAny :: (DotStatements n -> [a]) -> [Attributes] -> [DotStatements n] -> [Attributes] keepIfAny f sas = map fst . filter snd . zip sas . map (hasAny f) hasAny :: (DotStatements n -> [a]) -> DotStatements n -> Bool hasAny f ds = not (null $ f ds) || any (hasAny f . subGraphStmts) (subGraphs ds) promoteDSG :: DotSubGraph n -> DotGraph n promoteDSG dsg = DotGraph { strictGraph = undefined , directedGraph = undefined , graphID = subGraphID dsg , graphStatements = subGraphStmts dsg } -- Same as compare for lists, except shorter lists are GT compLists :: (Ord a) => [a] -> [a] -> Ordering compLists [] [] = EQ compLists [] _ = GT compLists _ [] = LT compLists (x:xs) (y:ys) = case compare x y of EQ -> compLists xs ys oth -> oth nonEmptyGAs :: [GlobalAttributes] -> [GlobalAttributes] nonEmptyGAs = filter (not . null . attrs) -- Assign each edge into the cluster it belongs in. edgeClusters :: (Ord n) => NodeLookup n -> [DotEdge n] -> EdgeLocations n edgeClusters nl = (toM *** map snd) . partition (not . null . fst) . map inClust where nl' = Map.map (F.toList . fst) nl -- DotEdge n -> (Path, DotEdge n) inClust de@(DotEdge n1 n2 _) = (flip (,) de) . map fst . takeWhile (uncurry (==)) $ zip (nl' Map.! n1) (nl' Map.! n2) toM = Map.map DList.toList . Map.fromListWith (flip DList.append) . map (last *** DList.singleton) -- ----------------------------------------------------------------------------- {- $transitive In large, cluttered graphs, it can often be difficult to see what is happening due to the number of edges being drawn. As such, it is often useful to remove transitive edges from the graph before visualising it. For example, consider the following Dot graph: > digraph { > a -> b; > a -> c; > b -> c; > } This graph has the transitive edge @a -> c@ (as we can reach @c@ from @a@ via @b@). Graphviz comes with the @tred@ program to perform these transitive reductions. 'transitiveReduction' and 'transitiveReductionOptions' are pure Haskell re-implementations of @tred@ with the following differences: * @tred@ prints a message to stderr if a cycle is detected; these functions do not. * @tred@ preserves the original structure of the graph; these functions use the canonicalisation functions above to create the new graph (rather than re-implement creation functions for each one). When a graph contains cycles, an arbitrary edge from that cycle is ignored whilst calculating the transitive reduction. Multiple edges are also reduced (such that only the first edge between two nodes is kept). Note that transitive reduction only makes sense for directed graphs; for undirected graphs these functions are identical to the canonicalisation functions above. The caveats for the canonicalisation functions also apply. -} transitiveReduction :: (DotRepr dg n) => dg n -> DotGraph n transitiveReduction = transitiveReductionOptions defaultCanonOptions transitiveReductionOptions :: (DotRepr dg n) => CanonicaliseOptions -> dg n -> DotGraph n transitiveReductionOptions opts dg = cdg { strictGraph = graphIsStrict dg , directedGraph = graphIsDirected dg } where cdg = createCanonical opts (getID dg) gas cl nl es' (gas, cl) = graphStructureInformationClean dg nl = nodeInformationClean True dg es = edgeInformationClean True dg es' | graphIsDirected dg = rmTransEdges es | otherwise = es rmTransEdges :: (Ord n) => [DotEdge n] -> [DotEdge n] rmTransEdges [] = [] rmTransEdges es = concatMap (map snd . outgoing) $ Map.elems esM where tes = tagEdges es esMS = do edgeGraph tes ns <- getsMap Map.keys mapM_ (traverseTag zeroTag) ns esM = fst $ execState esMS (Map.empty, Set.empty) type Tag = Int type TagSet = Set Int type TaggedEdge n = (Tag, DotEdge n) -- A "nonsense" tag to use as an initial value zeroTag :: Tag zeroTag = 0 tagEdges :: [DotEdge n] -> [TaggedEdge n] tagEdges = zip [(succ zeroTag)..] data TaggedValues n = TV { marked :: Bool , incoming :: [TaggedEdge n] , outgoing :: [TaggedEdge n] } deriving (Eq, Ord, Show, Read) defTV :: TaggedValues n defTV = TV False [] [] type TagMap n = Map n (TaggedValues n) type TagState n a = State (TagMap n, TagSet) a getMap :: TagState n (TagMap n) getMap = gets fst getsMap :: (TagMap n -> a) -> TagState n a getsMap f = gets (f . fst) modifyMap :: (TagMap n -> TagMap n) -> TagState n () modifyMap f = modify (first f) getSet :: TagState n TagSet getSet = gets snd modifySet :: (TagSet -> TagSet) -> TagState n () modifySet f = modify (second f) -- Create the Map representing the graph from the edges. edgeGraph :: (Ord n) => [TaggedEdge n] -> TagState n () edgeGraph = mapM_ addEdge . reverse where addEdge te = addVal f tvOut >> addVal t tvIn where e = snd te f = fromNode e t = toNode e addVal n tv = modifyMap (Map.insertWith mergeTV n tv) tvIn = defTV { incoming = [te] } tvOut = defTV { outgoing = [te] } mergeTV tvNew tv = tv { incoming = incoming tvNew ++ incoming tv , outgoing = outgoing tvNew ++ outgoing tv } -- Perform a DFS to determine whether or not to keep each edge. traverseTag :: (Ord n) => Tag -> n -> TagState n () traverseTag t n = do setMark True checkIncoming outEs <- getsMap (maybe [] outgoing . Map.lookup n) mapM_ maybeRecurse outEs setMark False where setMark mrk = modifyMap (Map.adjust (\tv -> tv { marked = mrk }) n) isMarked m n' = maybe False marked $ n' `Map.lookup` m checkIncoming = do m <- gets fst let es = incoming $ m Map.! n (keepEs, delEs) = partition (keepEdge m) es modifyMap (Map.adjust (\tv -> tv {incoming = keepEs}) n) modifySet (Set.union $ Set.fromList (map fst delEs)) mapM_ delOtherEdge delEs where keepEdge m (t',e) = t == t' || not (isMarked m $ fromNode e) delOtherEdge te = modifyMap (Map.adjust delE . fromNode $ snd te) where delE tv = tv {outgoing = deleteBy ((==) `on` fst) te $ outgoing tv} maybeRecurse (t',e) = do m <- getMap delSet <- getSet let n' = toNode e unless (isMarked m n' || t' `Set.member` delSet) $ traverseTag t' n' graphviz-2999.20.2.0/Data/GraphViz/Attributes/Internal.hs0000644000000000000000000001222114535166704021100 0ustar0000000000000000{-# LANGUAGE CPP, OverloadedStrings #-} {-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Attributes.Internal Description : Internal Attribute value definitions Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module is defined so as to avoid exposing internal functions in the external API. These are those that are needed for the testsuite. -} module Data.GraphViz.Attributes.Internal ( PortName(..) , PortPos(..) , CompassPoint(..) , compassLookup , parseEdgeBasedPP ) where import Data.GraphViz.Parsing import Data.GraphViz.Printing import Data.Map (Map) import qualified Data.Map as Map import Data.Maybe (isNothing) import Data.Text.Lazy (Text) #if !MIN_VERSION_base (4,13,0) import Data.Monoid ((<>)) #endif -- ----------------------------------------------------------------------------- -- Note that printing and parsing of PortName values is specific to -- where it's being used: record- and HTML-like labels print/parse -- them differently from when they're on they're part of PortPos; the -- default printing and parsing is done for the latter. -- Should this really be exported from here? Or in another common module? -- | Specifies a name for ports (used also in record-based and -- HTML-like labels). Note that it is not valid for a 'PortName' -- value to contain a colon (@:@) character; it is assumed that it -- doesn't. newtype PortName = PN { portName :: Text } deriving (Eq, Ord, Show, Read) instance PrintDot PortName where unqtDot = unqtDot . portName toDot = toDot . portName instance ParseDot PortName where parseUnqt = PN <$> parseEscaped False [] ['"', ':'] parse = quotedParse parseUnqt `onFail` unqtPortName unqtPortName :: Parse PortName unqtPortName = PN <$> quotelessString -- ----------------------------------------------------------------------------- data PortPos = LabelledPort PortName (Maybe CompassPoint) | CompassPoint CompassPoint deriving (Eq, Ord, Show, Read) instance PrintDot PortPos where unqtDot (LabelledPort n mc) = unqtDot n <> maybe empty (colon <>) (fmap unqtDot mc) unqtDot (CompassPoint cp) = unqtDot cp toDot (LabelledPort n Nothing) = toDot n toDot lp@LabelledPort{} = dquotes $ unqtDot lp toDot cp = unqtDot cp instance ParseDot PortPos where parseUnqt = do n <- parseUnqt mc <- optional $ character ':' >> parseUnqt return $ if isNothing mc then checkPortName n else LabelledPort n mc parse = quotedParse parseUnqt `onFail` fmap checkPortName unqtPortName checkPortName :: PortName -> PortPos checkPortName pn = maybe (LabelledPort pn Nothing) CompassPoint . (`Map.lookup` compassLookup) $ portName pn -- | When attached to a node in a DotEdge definition, the 'PortName' -- and the 'CompassPoint' can be in separate quotes. parseEdgeBasedPP :: Parse PortPos parseEdgeBasedPP = liftA2 LabelledPort parse (fmap Just $ character ':' *> parse) `onFail` parse data CompassPoint = North | NorthEast | East | SouthEast | South | SouthWest | West | NorthWest | CenterPoint | NoCP deriving (Eq, Ord, Bounded, Enum, Show, Read) instance PrintDot CompassPoint where unqtDot NorthEast = text "ne" unqtDot NorthWest = text "nw" unqtDot North = text "n" unqtDot East = text "e" unqtDot SouthEast = text "se" unqtDot SouthWest = text "sw" unqtDot South = text "s" unqtDot West = text "w" unqtDot CenterPoint = text "c" unqtDot NoCP = text "_" instance ParseDot CompassPoint where -- Have to take care of longer parsing values first. parseUnqt = oneOf [ stringRep NorthEast "ne" , stringRep NorthWest "nw" , stringRep North "n" , stringRep SouthEast "se" , stringRep SouthWest "sw" , stringRep South "s" , stringRep East "e" , stringRep West "w" , stringRep CenterPoint "c" , stringRep NoCP "_" ] compassLookup :: Map Text CompassPoint compassLookup = Map.fromList [ ("ne", NorthEast) , ("nw", NorthWest) , ("n", North) , ("e", East) , ("se", SouthEast) , ("sw", SouthWest) , ("s", South) , ("w", West) , ("c", CenterPoint) , ("_", NoCP) ] -- ----------------------------------------------------------------------------- graphviz-2999.20.2.0/Data/GraphViz/Internal/Util.hs0000644000000000000000000001421214535166704017671 0ustar0000000000000000{-# LANGUAGE CPP, OverloadedStrings, PatternGuards #-} {-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Internal.Util Description : Internal utility functions Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module defines internal utility functions. -} module Data.GraphViz.Internal.Util where import Data.Char (isAsciiLower, isAsciiUpper, isDigit, ord) import Control.Monad (liftM2) import Data.Function (on) import Data.List (groupBy, sortBy) import Data.Maybe (isJust) import Data.Set (Set) import qualified Data.Set as Set import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T import qualified Data.Text.Lazy.Read as T #if MIN_VERSION_base(4,8,0) import Data.Version (Version, makeVersion) #else import Data.Version (Version(..)) #endif -- ----------------------------------------------------------------------------- isIDString :: Text -> Bool isIDString = maybe False (\(f,os) -> frstIDString f && T.all restIDString os) . T.uncons -- | First character of a non-quoted 'String' must match this. frstIDString :: Char -> Bool frstIDString c = any ($c) [ isAsciiUpper , isAsciiLower , (==) '_' , (\ x -> ord x >= 128) ] -- | The rest of a non-quoted 'String' must match this. restIDString :: Char -> Bool restIDString c = frstIDString c || isDigit c -- | Determine if this String represents a number. Boolean parameter -- determines if exponents are considered part of numbers for this. isNumString :: Bool -> Text -> Bool isNumString _ "" = False isNumString _ "-" = False isNumString allowE str = case T.uncons $ T.toLower str of Just ('-',str') -> go str' _ -> go str where -- Can't use Data.Text.Lazy.Read.double as it doesn't cover all -- possible cases go s = uncurry go' $ T.span isDigit s go' ds nds | T.null nds = True | T.null ds && nds == "." = False | T.null ds , Just ('.',nds') <- T.uncons nds , Just (d,nds'') <- T.uncons nds' = isDigit d && checkEs' nds'' | Just ('.',nds') <- T.uncons nds = checkEs $ T.dropWhile isDigit nds' | T.null ds = False | otherwise = checkEs nds checkEs' s = case T.break ('e' ==) s of ("", _) -> False (ds,es) -> T.all isDigit ds && checkEs es checkEs str' = case T.uncons str' of Nothing -> True Just ('e',ds) -> allowE && isIntString ds _ -> False {- -- | This assumes that 'isNumString' is 'True'. toDouble :: Text -> Double toDouble str = case T.uncons $ T.toLower str of Just ('-', str') -> toD $ '-' `T.cons` adj str' _ -> toD $ adj str where adj s = T.cons '0' $ case T.span ('.' ==) s of (ds, ".") | not $ T.null ds -> s `T.snoc` '0' (ds, ds') | Just ('.',es) <- T.uncons ds' , Just ('e',es') <- T.uncons es -> ds `T.snoc` '.' `T.snoc` '0' `T.snoc` 'e' `T.snoc` '0' `T.append` es' _ -> s toD = either (const $ error "Not a Double") fst . T.signed T.double -} -- | This assumes that 'isNumString' is 'True'. toDouble :: Text -> Double toDouble str = case T.uncons $ T.toLower str of Just ('-', str') -> toD $ '-' `T.cons` adj str' _ -> toD $ adj str where adj s = T.cons '0' $ case T.span ('.' ==) s of (ds, ".") | not $ T.null ds -> s `T.snoc` '0' (ds, ds') | Just ('.',es) <- T.uncons ds' , Just ('e',_) <- T.uncons es -> ds `T.snoc` '.' `T.snoc` '0' `T.append` es _ -> s toD = read . T.unpack isIntString :: Text -> Bool isIntString = isJust . stringToInt -- | Determine if this String represents an integer. stringToInt :: Text -> Maybe Int stringToInt str = case T.signed T.decimal str of Right (n, "") -> Just n _ -> Nothing -- | Graphviz requires double quotes to be explicitly escaped. escapeQuotes :: String -> String escapeQuotes [] = [] escapeQuotes ('"':str) = '\\':'"': escapeQuotes str escapeQuotes (c:str) = c : escapeQuotes str -- | Remove explicit escaping of double quotes. descapeQuotes :: String -> String descapeQuotes [] = [] descapeQuotes ('\\':'"':str) = '"' : descapeQuotes str descapeQuotes (c:str) = c : descapeQuotes str isKeyword :: Text -> Bool isKeyword = (`Set.member` keywords) . T.toLower -- | The following are Dot keywords and are not valid as labels, etc. unquoted. keywords :: Set Text keywords = Set.fromList [ "node" , "edge" , "graph" , "digraph" , "subgraph" , "strict" ] createVersion :: [Int] -> Version #if MIN_VERSION_base(4,8,0) createVersion = makeVersion #else createVersion bs = Version { versionBranch = bs, versionTags = []} #endif -- ----------------------------------------------------------------------------- uniq :: (Ord a) => [a] -> [a] uniq = uniqBy id uniqBy :: (Ord b) => (a -> b) -> [a] -> [a] uniqBy f = map head . groupSortBy f groupSortBy :: (Ord b) => (a -> b) -> [a] -> [[a]] groupSortBy f = groupBy ((==) `on` f) . sortBy (compare `on` f) groupSortCollectBy :: (Ord b) => (a -> b) -> (a -> c) -> [a] -> [(b,[c])] groupSortCollectBy f g = map (liftM2 (,) (f . head) (map g)) . groupSortBy f -- | Fold over 'Bool's; first param is for 'False', second for 'True'. bool :: a -> a -> Bool -> a bool f t b = if b then t else f isSingle :: [a] -> Bool isSingle [_] = True isSingle _ = False graphviz-2999.20.2.0/Data/GraphViz/Internal/State.hs0000644000000000000000000001170614535166704020041 0ustar0000000000000000{-# OPTIONS_HADDOCK hide #-} {-# LANGUAGE FlexibleInstances #-} {- | Module : Data.GraphViz.Internal.State Description : Printing and parsing state. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com When printing and parsing Dot code, some items depend on values that are set earlier. -} module Data.GraphViz.Internal.State ( GraphvizStateM(..) , GraphvizState(..) , AttributeType(..) , setAttributeType , getAttributeType , initialState , setDirectedness , getDirectedness , setLayerSep , getLayerSep , setLayerListSep , getLayerListSep , setColorScheme , getColorScheme ) where import Data.GraphViz.Attributes.ColorScheme import Text.ParserCombinators.Poly.StateText (Parser, stQuery, stUpdate) -- ----------------------------------------------------------------------------- class (Monad m) => GraphvizStateM m where modifyGS :: (GraphvizState -> GraphvizState) -> m () getsGS :: (GraphvizState -> a) -> m a instance GraphvizStateM (Parser GraphvizState) where modifyGS = stUpdate getsGS = stQuery data AttributeType = GraphAttribute | SubGraphAttribute | ClusterAttribute | NodeAttribute | EdgeAttribute deriving (Eq, Ord, Show, Read) -- | Several aspects of Dot code are either global or mutable state. data GraphvizState = GS { parseStrictly :: !Bool -- ^ If 'False', allow fallbacks for -- attributes that don't match known -- specification when parsing. , directedEdges :: !Bool , layerSep :: [Char] , layerListSep :: [Char] , attributeType :: !AttributeType , graphColor :: !ColorScheme , clusterColor :: !ColorScheme , nodeColor :: !ColorScheme , edgeColor :: !ColorScheme } deriving (Eq, Ord, Show, Read) initialState :: GraphvizState initialState = GS { parseStrictly = True , directedEdges = True , layerSep = defLayerSep , layerListSep = defLayerListSep , attributeType = GraphAttribute , graphColor = X11 , clusterColor = X11 , nodeColor = X11 , edgeColor = X11 } setDirectedness :: (GraphvizStateM m) => Bool -> m () setDirectedness d = modifyGS (\ gs -> gs { directedEdges = d } ) getDirectedness :: (GraphvizStateM m) => m Bool getDirectedness = getsGS directedEdges setAttributeType :: (GraphvizStateM m) => AttributeType -> m () setAttributeType tp = modifyGS $ \ gs -> gs { attributeType = tp } getAttributeType :: (GraphvizStateM m) => m AttributeType getAttributeType = getsGS attributeType setLayerSep :: (GraphvizStateM m) => [Char] -> m () setLayerSep sep = modifyGS (\ gs -> gs { layerSep = sep } ) getLayerSep :: (GraphvizStateM m) => m [Char] getLayerSep = getsGS layerSep setLayerListSep :: (GraphvizStateM m) => [Char] -> m () setLayerListSep sep = modifyGS (\ gs -> gs { layerListSep = sep } ) getLayerListSep :: (GraphvizStateM m) => m [Char] getLayerListSep = getsGS layerListSep setColorScheme :: (GraphvizStateM m) => ColorScheme -> m () setColorScheme cs = do tp <- getsGS attributeType modifyGS $ \gs -> case tp of GraphAttribute -> gs { graphColor = cs } -- subgraphs don't have specified scheme SubGraphAttribute -> gs { graphColor = cs } ClusterAttribute -> gs { clusterColor = cs } NodeAttribute -> gs { nodeColor = cs } EdgeAttribute -> gs { edgeColor = cs } getColorScheme :: (GraphvizStateM m) => m ColorScheme getColorScheme = do tp <- getsGS attributeType getsGS $ case tp of GraphAttribute -> graphColor -- subgraphs don't have specified scheme SubGraphAttribute -> graphColor ClusterAttribute -> clusterColor NodeAttribute -> nodeColor EdgeAttribute -> edgeColor -- | The default separators for -- 'Data.GraphViz.Attributes.Complete.LayerSep'. defLayerSep :: [Char] defLayerSep = [' ', ':', '\t'] -- | The default separators for -- 'Data.GraphViz.Attributes.Complete.LayerListSep'. defLayerListSep :: [Char] defLayerListSep = [','] graphviz-2999.20.2.0/Data/GraphViz/Types/Internal/Common.hs0000644000000000000000000005031414535166704021313 0ustar0000000000000000{-# LANGUAGE CPP, OverloadedStrings #-} {-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Types.Internal.Common Description : Common internal functions for dealing with overall types. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module provides common functions used by both "Data.GraphViz.Types" as well as "Data.GraphViz.Types.Generalised". -} module Data.GraphViz.Types.Internal.Common ( GraphID (..) , Number (..) , numericValue , GlobalAttributes (..) , partitionGlobal , unPartitionGlobal , withGlob , DotNode (..) , DotEdge (..) , parseEdgeLine , printGraphID , parseGraphID , printStmtBased , printStmtBasedList , printSubGraphID , parseSubGraph , parseBracesBased , parseStatements ) where import Data.GraphViz.Attributes.Complete (Attribute(HeadPort, TailPort), Attributes, Number(..), usedByClusters, usedByGraphs, usedByNodes) import Data.GraphViz.Attributes.Internal (PortPos, parseEdgeBasedPP) import Data.GraphViz.Internal.State import Data.GraphViz.Internal.Util import Data.GraphViz.Parsing import Data.GraphViz.Printing import Control.Monad (unless, when) import Data.Maybe (isJust) import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T import qualified Data.Text.Lazy.Read as T #if !MIN_VERSION_base (4,13,0) import Data.Monoid ((<>)) #endif -- ----------------------------------------------------------------------------- -- This is re-exported by Data.GraphViz.Types -- | A polymorphic type that covers all possible ID values allowed by -- Dot syntax. Note that whilst the 'ParseDot' and 'PrintDot' -- instances for 'String' will properly take care of the special -- cases for numbers, they are treated differently here. data GraphID = Str Text | Num Number deriving (Eq, Ord, Show, Read) instance PrintDot GraphID where unqtDot (Str str) = unqtDot str unqtDot (Num n) = unqtDot n toDot (Str str) = toDot str toDot (Num n) = toDot n instance ParseDot GraphID where parseUnqt = stringNum <$> parseUnqt parse = stringNum <$> parse `adjustErr` ("Not a valid GraphID\n\t"++) stringNum :: Text -> GraphID stringNum str = maybe checkDbl (Num . Int) $ stringToInt str where checkDbl = if isNumString True str then Num . Dbl $ toDouble str else Str str numericValue :: GraphID -> Maybe Int numericValue (Str str) = either (const Nothing) (Just . round . fst) $ T.signed T.double str numericValue (Num n) = case n of Int i -> Just i Dbl d -> Just $ round d -- ----------------------------------------------------------------------------- -- Re-exported by Data.GraphViz.Types.* -- | Represents a list of top-level list of 'Attribute's for the -- entire graph/sub-graph. Note that 'GraphAttrs' also applies to -- 'DotSubGraph's. -- -- Note that Dot allows a single 'Attribute' to be listed on a line; -- if this is the case then when parsing, the type of 'Attribute' it -- is determined and that type of 'GlobalAttribute' is created. data GlobalAttributes = GraphAttrs { attrs :: Attributes } | NodeAttrs { attrs :: Attributes } | EdgeAttrs { attrs :: Attributes } deriving (Eq, Ord, Show, Read) instance PrintDot GlobalAttributes where unqtDot = printAttrBased True printGlobAttrType globAttrType attrs unqtListToDot = printAttrBasedList True printGlobAttrType globAttrType attrs listToDot = unqtListToDot -- GraphAttrs, NodeAttrs and EdgeAttrs respectively partitionGlobal :: [GlobalAttributes] -> (Attributes, Attributes, Attributes) partitionGlobal = foldr select ([], [], []) where select globA ~(gs,ns,es) = case globA of GraphAttrs as -> (as ++ gs, ns, es) NodeAttrs as -> (gs, as ++ ns, es) EdgeAttrs as -> (gs, ns, as ++ es) unPartitionGlobal :: (Attributes, Attributes, Attributes) -> [GlobalAttributes] unPartitionGlobal (gas,nas,eas) = [ GraphAttrs gas , NodeAttrs nas , EdgeAttrs eas ] printGlobAttrType :: GlobalAttributes -> DotCode printGlobAttrType GraphAttrs{} = text "graph" printGlobAttrType NodeAttrs{} = text "node" printGlobAttrType EdgeAttrs{} = text "edge" instance ParseDot GlobalAttributes where -- Not using parseAttrBased here because we want to force usage of -- Attributes. parseUnqt = do gat <- parseGlobAttrType -- Determine if we need to set the attribute type. let mtp = globAttrType $ gat [] -- Only need the constructor oldTp <- getAttributeType maybe (return ()) setAttributeType mtp as <- whitespace *> parse -- Safe to set back even if not changed. setAttributeType oldTp return $ gat as `onFail` fmap determineType parse parse = parseUnqt -- Don't want the option of quoting `adjustErr` ("Not a valid listing of global attributes\n\t"++) -- Have to do this manually because of the special case parseUnqtList = parseStatements parseUnqt parseList = parseUnqtList -- Cheat: rather than determine whether it's a graph, cluster or -- sub-graph just don't set it. globAttrType :: GlobalAttributes -> Maybe AttributeType globAttrType NodeAttrs{} = Just NodeAttribute globAttrType EdgeAttrs{} = Just EdgeAttribute globAttrType _ = Nothing parseGlobAttrType :: Parse (Attributes -> GlobalAttributes) parseGlobAttrType = oneOf [ stringRep GraphAttrs "graph" , stringRep NodeAttrs "node" , stringRep EdgeAttrs "edge" ] determineType :: Attribute -> GlobalAttributes determineType attr | usedByGraphs attr = GraphAttrs attr' | usedByClusters attr = GraphAttrs attr' -- Also covers SubGraph case | usedByNodes attr = NodeAttrs attr' | otherwise = EdgeAttrs attr' -- Must be for edges. where attr' = [attr] withGlob :: (Attributes -> Attributes) -> GlobalAttributes -> GlobalAttributes withGlob f (GraphAttrs as) = GraphAttrs $ f as withGlob f (NodeAttrs as) = NodeAttrs $ f as withGlob f (EdgeAttrs as) = EdgeAttrs $ f as -- ----------------------------------------------------------------------------- -- | A node in 'DotGraph'. data DotNode n = DotNode { nodeID :: n , nodeAttributes :: Attributes } deriving (Eq, Ord, Show, Read) instance (PrintDot n) => PrintDot (DotNode n) where unqtDot = printAttrBased False printNodeID (const $ Just NodeAttribute) nodeAttributes unqtListToDot = printAttrBasedList False printNodeID (const $ Just NodeAttribute) nodeAttributes listToDot = unqtListToDot printNodeID :: (PrintDot n) => DotNode n -> DotCode printNodeID = toDot . nodeID instance (ParseDot n) => ParseDot (DotNode n) where parseUnqt = parseAttrBased NodeAttribute False parseNodeID parse = parseUnqt -- Don't want the option of quoting parseUnqtList = parseAttrBasedList NodeAttribute False parseNodeID parseList = parseUnqtList parseNodeID :: (ParseDot n) => Parse (Attributes -> DotNode n) parseNodeID = DotNode <$> parseAndCheck where parseAndCheck = do n <- parse me <- optional parseUnwanted maybe (return n) (const notANode) me notANode = fail "This appears to be an edge, not a node" parseUnwanted = oneOf [ parseEdgeType *> return () , character ':' *> return () -- PortPos value ] instance Functor DotNode where fmap f n = n { nodeID = f $ nodeID n } -- ----------------------------------------------------------------------------- -- This is re-exported in Data.GraphViz.Types; defined here so that -- Generalised can access and use parseEdgeLine (needed for "a -> b -> -- c"-style edge statements). -- | An edge in 'DotGraph'. data DotEdge n = DotEdge { fromNode :: n , toNode :: n , edgeAttributes :: Attributes } deriving (Eq, Ord, Show, Read) instance (PrintDot n) => PrintDot (DotEdge n) where unqtDot = printAttrBased False printEdgeID (const $ Just EdgeAttribute) edgeAttributes unqtListToDot = printAttrBasedList False printEdgeID (const $ Just EdgeAttribute) edgeAttributes listToDot = unqtListToDot printEdgeID :: (PrintDot n) => DotEdge n -> DotCode printEdgeID e = do isDir <- getDirectedness toDot (fromNode e) <+> bool undirEdge' dirEdge' isDir <+> toDot (toNode e) instance (ParseDot n) => ParseDot (DotEdge n) where parseUnqt = parseAttrBased EdgeAttribute False parseEdgeID parse = parseUnqt -- Don't want the option of quoting -- Have to take into account edges of the type "n1 -> n2 -> n3", etc. parseUnqtList = concat <$> parseStatements parseEdgeLine parseList = parseUnqtList parseEdgeID :: (ParseDot n) => Parse (Attributes -> DotEdge n) parseEdgeID = ignoreSep mkEdge parseEdgeNode parseEdgeType parseEdgeNode `adjustErr` ("Parsed beginning of DotEdge but could not parse Attributes:\n\t"++) -- Parse both edge types just to be more liberal type EdgeNode n = (n, Maybe PortPos) -- | Takes into account edge statements containing something like -- @a -> \{b c\}@. parseEdgeNodes :: (ParseDot n) => Parse [EdgeNode n] parseEdgeNodes = oneOf [ parseBraced (wrapWhitespace -- Should really use sepBy1, but this will do. $ parseStatements parseEdgeNode) , sepBy1 parseEdgeNode (wrapWhitespace parseComma) , (: []) <$> parseEdgeNode ] parseEdgeNode :: (ParseDot n) => Parse (EdgeNode n) parseEdgeNode = liftA2 (,) parse (optional $ character ':' *> parseEdgeBasedPP) mkEdge :: EdgeNode n -> EdgeNode n -> Attributes -> DotEdge n mkEdge (eFrom, mFP) (eTo, mTP) = DotEdge eFrom eTo . addPortPos TailPort mFP . addPortPos HeadPort mTP mkEdges :: [EdgeNode n] -> [EdgeNode n] -> Attributes -> [DotEdge n] mkEdges fs ts as = liftA2 (\f t -> mkEdge f t as) fs ts addPortPos :: (PortPos -> Attribute) -> Maybe PortPos -> Attributes -> Attributes addPortPos c = maybe id ((:) . c) parseEdgeType :: Parse Bool parseEdgeType = wrapWhitespace $ stringRep True dirEdge `onFail` stringRep False undirEdge parseEdgeLine :: (ParseDot n) => Parse [DotEdge n] parseEdgeLine = do n1 <- parseEdgeNodes ens <- many1 $ parseEdgeType *> parseEdgeNodes let ens' = n1 : ens efs = zipWith mkEdges ens' (tail ens') ef = return $ \ as -> concatMap ($as) efs parseAttrBased EdgeAttribute False ef instance Functor DotEdge where fmap f e = e { fromNode = f $ fromNode e , toNode = f $ toNode e } dirEdge :: String dirEdge = "->" dirEdge' :: DotCode dirEdge' = text $ T.pack dirEdge undirEdge :: String undirEdge = "--" undirEdge' :: DotCode undirEdge' = text $ T.pack undirEdge -- ----------------------------------------------------------------------------- -- Labels dirGraph :: String dirGraph = "digraph" dirGraph' :: DotCode dirGraph' = text $ T.pack dirGraph undirGraph :: String undirGraph = "graph" undirGraph' :: DotCode undirGraph' = text $ T.pack undirGraph strGraph :: String strGraph = "strict" strGraph' :: DotCode strGraph' = text $ T.pack strGraph sGraph :: String sGraph = "subgraph" sGraph' :: DotCode sGraph' = text $ T.pack sGraph clust :: String clust = "cluster" clust' :: DotCode clust' = text $ T.pack clust -- ----------------------------------------------------------------------------- printGraphID :: (a -> Bool) -> (a -> Bool) -> (a -> Maybe GraphID) -> a -> DotCode printGraphID str isDir mID g = do setDirectedness isDir' bool empty strGraph' (str g) <+> bool undirGraph' dirGraph' isDir' <+> maybe empty toDot (mID g) where isDir' = isDir g parseGraphID :: (Bool -> Bool -> Maybe GraphID -> a) -> Parse a parseGraphID f = do whitespace str <- isJust <$> optional (parseAndSpace $ string strGraph) dir <- parseAndSpace ( stringRep True dirGraph `onFail` stringRep False undirGraph ) setDirectedness dir gID <- optional $ parseAndSpace parse return $ f str dir gID printStmtBased :: (a -> DotCode) -> (a -> AttributeType) -> (a -> stmts) -> (stmts -> DotCode) -> a -> DotCode printStmtBased f ftp r dr a = do gs <- getsGS id setAttributeType $ ftp a dc <- printBracesBased (f a) (dr $ r a) modifyGS (const gs) return dc printStmtBasedList :: (a -> DotCode) -> (a -> AttributeType) -> (a -> stmts) -> (stmts -> DotCode) -> [a] -> DotCode printStmtBasedList f ftp r dr = vcat . mapM (printStmtBased f ftp r dr) -- Can't use the 'braces' combinator here because we want the closing -- brace lined up with the h value, which due to indentation might not -- be the case with braces. printBracesBased :: DotCode -> DotCode -> DotCode printBracesBased h i = vcat $ sequence [ h <+> lbrace , ind i , rbrace ] where ind = indent 4 -- | This /must/ only be used for sub-graphs, etc. parseBracesBased :: AttributeType -> Parse a -> Parse a parseBracesBased tp p = do gs <- getsGS id setAttributeType tp a <- whitespace *> parseBraced (wrapWhitespace p) modifyGS (const gs) return a `adjustErr` ("Not a valid value wrapped in braces.\n\t"++) printSubGraphID :: (a -> (Bool, Maybe GraphID)) -> a -> DotCode printSubGraphID f a = sGraph' <+> maybe cl dtID mID where (isCl, mID) = f a cl = bool empty clust' isCl dtID = printSGID isCl -- | Print the actual ID for a 'DotSubGraph'. printSGID :: Bool -> GraphID -> DotCode printSGID isCl sID = bool noClust addClust isCl where noClust = toDot sID -- Have to manually render it as we need the un-quoted form. addClust = toDot . T.append (T.pack clust) . T.cons '_' . renderDot $ mkDot sID mkDot (Str str) = text str -- Quotes will be escaped later mkDot gid = unqtDot gid parseSubGraph :: (Bool -> Maybe GraphID -> stmt -> c) -> Parse stmt -> Parse c parseSubGraph pid pst = do (isC, fID) <- parseSubGraphID pid let tp = bool SubGraphAttribute ClusterAttribute isC fID <$> parseBracesBased tp pst parseSubGraphID :: (Bool -> Maybe GraphID -> c) -> Parse (Bool,c) parseSubGraphID f = appl <$> (string sGraph *> whitespace1 *> parseSGID) where appl (isC, mid) = (isC, f isC mid) parseSGID :: Parse (Bool, Maybe GraphID) parseSGID = oneOf [ getClustFrom <$> parseAndSpace parse , return (False, Nothing) ] where -- If it's a String value, check to see if it's actually a -- cluster_Blah value; thus need to manually re-parse it. getClustFrom (Str str) = runParser' pStr str getClustFrom gid = (False, Just gid) checkCl = stringRep True clust pStr = do isCl <- checkCl `onFail` return False when isCl $ optional (character '_') *> return () sID <- optional pID let sID' = if sID == emptyID then Nothing else sID return (isCl, sID') emptyID = Just $ Str "" -- For Strings, there are no more quotes to unescape, so consume -- what you can. pID = stringNum <$> manySatisfy (const True) {- This is a much nicer definition, but unfortunately it doesn't work. The problem is that Graphviz decides that a subgraph is a cluster if the ID starts with "cluster" (no quotes); thus, we _have_ to do the double layer of parsing to get it to work :@ do isCl <- stringRep True clust `onFail` return False sID <- optional $ do when isCl $ optional (character '_') *> return () parseUnqt when (isCl || isJust sID) $ whitespace1 *> return () return (isCl, sID) -} -- The Bool is True for global, False for local. printAttrBased :: Bool -> (a -> DotCode) -> (a -> Maybe AttributeType) -> (a -> Attributes) -> a -> DotCode printAttrBased prEmp ff ftp fas a = do oldType <- getAttributeType maybe (return ()) setAttributeType mtp oldCS <- getColorScheme (dc <> semi) <* unless prEmp (setColorScheme oldCS) <* setAttributeType oldType where mtp = ftp a f = ff a dc = case fas a of [] | not prEmp -> f as -> f <+> toDot as -- The Bool is True for global, False for local. printAttrBasedList :: Bool -> (a -> DotCode) -> (a -> Maybe AttributeType) -> (a -> Attributes) -> [a] -> DotCode printAttrBasedList prEmp ff ftp fas = vcat . mapM (printAttrBased prEmp ff ftp fas) -- The Bool is True for global, False for local. parseAttrBased :: AttributeType -> Bool -> Parse (Attributes -> a) -> Parse a parseAttrBased tp lc p = do oldType <- getAttributeType setAttributeType tp oldCS <- getColorScheme f <- p atts <- tryParseList' (whitespace *> parse) unless lc $ setColorScheme oldCS when (tp /= oldType) $ setAttributeType oldType return $ f atts `adjustErr` ("Not a valid attribute-based structure\n\t"++) -- The Bool is True for global, False for local. parseAttrBasedList :: AttributeType -> Bool -> Parse (Attributes -> a) -> Parse [a] parseAttrBasedList tp lc = parseStatements . parseAttrBased tp lc -- | Parse the separator (and any other whitespace1 present) between statements. statementEnd :: Parse () statementEnd = parseSplit *> newline' where parseSplit = (whitespace *> oneOf [ character ';' *> return () , newline ] ) `onFail` whitespace1 parseStatements :: Parse a -> Parse [a] parseStatements p = sepBy (whitespace *> p) statementEnd `discard` optional statementEnd graphviz-2999.20.2.0/Data/GraphViz/Algorithms/Clustering.hs0000644000000000000000000001046414535166704021435 0ustar0000000000000000{-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Algorithms.Clustering Description : Definition of the clustering types for Graphviz. Copyright : (c) Matthew Sackman, Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module defines types for creating clusters. -} module Data.GraphViz.Algorithms.Clustering ( NodeCluster(..) , clustersToNodes ) where import Data.GraphViz.Types.Canonical import Data.GraphViz.Attributes.Complete(Attributes) import Data.Either(partitionEithers) import Data.List(groupBy, sortBy) -- ----------------------------------------------------------------------------- -- | Define into which cluster a particular node belongs. -- Clusters can be nested to arbitrary depth. data NodeCluster c a = N a -- ^ Indicates the actual Node in the Graph. | C c (NodeCluster c a) -- ^ Indicates that the -- 'NodeCluster' is in -- the Cluster /c/. deriving (Show) -- | Extract the clusters and nodes from the list of nodes. clustersToNodes :: (Ord c) => ((n,a) -> NodeCluster c (n,l)) -> (c -> Bool) -> (c -> GraphID) -> (c -> [GlobalAttributes]) -> ((n,l) -> Attributes) -> [(n,a)] -> ([DotSubGraph n], [DotNode n]) clustersToNodes clusterBy isC cID fmtCluster fmtNode = treesToDot isC cID fmtCluster fmtNode . collapseNClusts . map (clustToTree . clusterBy) -- ----------------------------------------------------------------------------- -- | A tree representation of a cluster. data ClusterTree c a = NT a | CT c [ClusterTree c a] deriving (Show) -- | Convert a single node cluster into its tree representation. clustToTree :: NodeCluster c a -> ClusterTree c a clustToTree (N ln) = NT ln clustToTree (C c nc) = CT c [clustToTree nc] -- | Two nodes are in the same "default" cluster; otherwise check if they -- are in the same cluster. sameClust :: (Eq c) => ClusterTree c a -> ClusterTree c a -> Bool sameClust (NT _) (NT _) = True sameClust (CT c1 _) (CT c2 _) = c1 == c2 sameClust _ _ = False -- | Singleton nodes come first, and then ordering based upon the cluster. clustOrder :: (Ord c) => ClusterTree c a -> ClusterTree c a -> Ordering clustOrder (NT _) (NT _) = EQ clustOrder (NT _) (CT _ _) = LT clustOrder (CT _ _) (NT _) = GT clustOrder (CT c1 _) (CT c2 _) = compare c1 c2 -- | Extract the sub-trees. getNodes :: ClusterTree c a -> [ClusterTree c a] getNodes n@(NT _) = [n] getNodes (CT _ ns) = ns -- | Combine clusters. collapseNClusts :: (Ord c) => [ClusterTree c a] -> [ClusterTree c a] collapseNClusts = concatMap grpCls . groupBy sameClust . sortBy clustOrder where grpCls [] = [] grpCls ns@(NT _ : _) = ns grpCls cs@(CT c _ : _) = [CT c (collapseNClusts $ concatMap getNodes cs)] -- | Convert the cluster representation of the trees into 'DotNode's -- and 'DotSubGraph's (with @'isCluster' = 'True'@, and -- @'subGraphID' = 'Nothing'@). treesToDot :: (c -> Bool) -> (c -> GraphID) -> (c -> [GlobalAttributes]) -> ((n,a) -> Attributes) -> [ClusterTree c (n,a)] -> ([DotSubGraph n], [DotNode n]) treesToDot isC cID fmtCluster fmtNode = partitionEithers . map (treeToDot isC cID fmtCluster fmtNode) -- | Convert this 'ClusterTree' into its /Dot/ representation. treeToDot :: (c -> Bool) -> (c -> GraphID) -> (c -> [GlobalAttributes]) -> ((n,a) -> Attributes) -> ClusterTree c (n,a) -> Either (DotSubGraph n) (DotNode n) treeToDot _ _ _ fmtNode (NT ln) = Right DotNode { nodeID = fst ln , nodeAttributes = fmtNode ln } treeToDot isC cID fmtCluster fmtNode (CT c nts) = Left DotSG { isCluster = isC c , subGraphID = Just $ cID c , subGraphStmts = stmts } where stmts = DotStmts { attrStmts = fmtCluster c , subGraphs = cs , nodeStmts = ns , edgeStmts = [] } (cs, ns) = treesToDot isC cID fmtCluster fmtNode nts graphviz-2999.20.2.0/Data/GraphViz/Attributes/Arrows.hs0000644000000000000000000001166114535166704020610 0ustar0000000000000000{-# LANGUAGE CPP, OverloadedStrings #-} {-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Attributes.Arrows Description : Arrow types Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Attributes.Arrows where import Data.GraphViz.Internal.Util (bool) import Data.GraphViz.Parsing import Data.GraphViz.Printing import Data.Maybe (isJust) #if !MIN_VERSION_base (4,13,0) import Data.Monoid ((<>)) #endif -- ----------------------------------------------------------------------------- -- | /Dot/ has a basic grammar of arrow shapes which allows usage of -- up to 1,544,761 different shapes from 9 different basic -- 'ArrowShape's. Note that whilst an explicit list is used in the -- definition of 'ArrowType', there must be at least one tuple and a -- maximum of 4 (since that is what is required by Dot). For more -- information, see: -- -- The 19 basic arrows shown on the overall attributes page have -- been defined below as a convenience. Parsing of the 5 -- backward-compatible special cases is also supported. newtype ArrowType = AType [(ArrowModifier, ArrowShape)] deriving (Eq, Ord, Show, Read) -- Used for default normal :: ArrowType normal = AType [(noMods, Normal)] -- Used for backward-compatible parsing 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) ] -- | What modifications to apply to an 'ArrowShape'. data ArrowModifier = ArrMod { arrowFill :: ArrowFill , arrowSide :: ArrowSide } deriving (Eq, Ord, Show, Read) -- | Apply no modifications to an 'ArrowShape'. noMods :: ArrowModifier noMods = ArrMod FilledArrow BothSides -- | 'OpenArrow' and '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') -- Not used individually parse = parseUnqt -- | Represents which side (when looking towards the node the arrow is -- pointing to) is drawn. 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') -- Not used individually parse = parseUnqt graphviz-2999.20.2.0/Data/GraphViz/Attributes/ColorScheme.hs0000644000000000000000000000517314535166704021537 0ustar0000000000000000{-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Attributes.ColorScheme Description : Specification of color schemes. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This is an internal module designed so that the state can record the current color scheme. -} module Data.GraphViz.Attributes.ColorScheme where import Data.Word(Word8) -- ----------------------------------------------------------------------------- -- | This represents the color schemes that Graphviz accepts. data ColorScheme = X11 | SVG | Brewer BrewerScheme deriving (Eq, Ord, Show, Read) -- | Specify which colour palette and how many colours it has. Note -- the allowed values for the different 'BrewerName's. data BrewerScheme = BScheme BrewerName Word8 deriving (Eq, Ord, Show, Read) -- | All of these have a minimum level value of @3@, with a maximum -- of @9@ unless otherwise specified. data BrewerName = Accent -- ^ Maximum of @8@. | Blues | Brbg -- ^ Maximum of @11@. | Bugn | Bupu | Dark2 -- ^ Maximum of @8@. | Gnbu | Greens | Greys | Oranges | Orrd | Paired -- ^ Maximum of @12@. | Pastel1 | Pastel2 -- ^ Maximum of @8@. | Piyg -- ^ Maximum of @11@. | Prgn -- ^ Maximum of @11@. | Pubu | Pubugn | Puor -- ^ Maximum of @11@; note that the last two are listed -- after the @'Purd'@ values in the -- documentation. | Purd | Purples | Rdbu -- ^ Maximum of @11@; note that the last two are listed -- first. | Rdgy -- ^ Maximum of @11@; note that the last two are listed -- after the @'Rdpu'@ values in the -- documentation. | Rdpu | Rdylbu -- ^ Maximum of @11@. | Rdylgn -- ^ Maximum of @11@. | Reds | Set1 | Set2 -- ^ Maximum of @8@. | Set3 -- ^ Maximum of @12@. | Spectral -- ^ Maximum of @11@. | Ylgn | Ylgnbu | Ylorbr | Ylorrd deriving (Eq, Ord, Bounded, Enum, Show, Read) graphviz-2999.20.2.0/Data/GraphViz/Attributes/Same.hs0000644000000000000000000000263314535166704020217 0ustar0000000000000000{-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Attributes.Same Description : Consider Attributes equal on constructors. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module is used when @a1 == a2@ should return @True@ if they are the same Attribute, even if they don't have the same value (typically for 'Set's). -} module Data.GraphViz.Attributes.Same ( SameAttr , SAttrs , toSAttr , unSame , unSameSet ) where import Data.GraphViz.Attributes.Complete(Attribute, Attributes, sameAttribute) import Data.Function(on) import qualified Data.Set as Set import Data.Set(Set) -- ----------------------------------------------------------------------------- -- | Defined as a wrapper around 'Attribute' where equality is based -- solely upon the constructor, not the contents. newtype SameAttr = SA { getAttr :: Attribute } deriving (Show, Read) instance Eq SameAttr where (==) = sameAttribute `on` getAttr instance Ord SameAttr where compare sa1 sa2 | sa1 == sa2 = EQ | otherwise = (compare `on` getAttr) sa1 sa2 type SAttrs = Set SameAttr toSAttr :: Attributes -> SAttrs toSAttr = Set.fromList . map SA unSame :: SAttrs -> Attributes unSame = map getAttr . Set.toList unSameSet :: SAttrs -> Set Attribute unSameSet = Set.mapMonotonic getAttr graphviz-2999.20.2.0/Data/GraphViz/Attributes/Values.hs0000644000000000000000000016345014535166704020576 0ustar0000000000000000{-# LANGUAGE CPP, OverloadedStrings #-} {-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Attributes.Values Description : Values for use with the Attribute data type Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com Defined to have smaller modules and thus faster compilation times. -} module Data.GraphViz.Attributes.Values where import qualified Data.GraphViz.Attributes.HTML as Html import Data.GraphViz.Attributes.Internal import Data.GraphViz.Internal.State (getLayerListSep, getLayerSep, setLayerListSep, setLayerSep) import Data.GraphViz.Internal.Util (bool, stringToInt) import Data.GraphViz.Parsing import Data.GraphViz.Printing import Data.List (intercalate) import Data.Maybe (isJust) import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T import Data.Word (Word16) import System.FilePath (searchPathSeparator, splitSearchPath) #if !MIN_VERSION_base (4,13,0) import Data.Monoid ((<>)) #endif -- ----------------------------------------------------------------------------- {- | Some 'Attribute's (mainly label-like ones) take a 'String' argument that allows for extra escape codes. This library doesn't do any extra checks or special parsing for these escape codes, but usage of 'EscString' rather than 'Text' indicates that the Graphviz tools will recognise these extra escape codes for these 'Attribute's. The extra escape codes include (note that these are all Strings): [@\\N@] Replace with the name of the node (for Node 'Attribute's). [@\\G@] Replace with the name of the graph (for Node 'Attribute's) or the name of the graph or cluster, whichever is applicable (for Graph, Cluster and Edge 'Attribute's). [@\\E@] Replace with the name of the edge, formed by the two adjoining nodes and the edge type (for Edge 'Attribute's). [@\\T@] Replace with the name of the tail node (for Edge 'Attribute's). [@\\H@] Replace with the name of the head node (for Edge 'Attribute's). [@\\L@] Replace with the object's label (for all 'Attribute's). Also, if the 'Attribute' in question is 'Label', 'HeadLabel' or 'TailLabel', then @\\n@, @\\l@ and @\\r@ split the label into lines centered, left-justified and right-justified respectively. -} type EscString = Text -- ----------------------------------------------------------------------------- -- | Should only have 2D points (i.e. created with 'createPoint'). 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 -- ----------------------------------------------------------------------------- -- | If 'Local', then sub-graphs that are clusters are given special -- treatment. 'Global' and 'NoCluster' currently appear to be -- identical and turn off the special cluster processing. 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" ] -- ----------------------------------------------------------------------------- -- | Specify where to place arrow heads on an edge. data DirType = Forward -- ^ Draw a directed edge with an arrow to the -- node it's pointing go. | Back -- ^ Draw a reverse directed edge with an arrow -- to the node it's coming from. | Both -- ^ Draw arrows on both ends of the edge. | NoDir -- ^ Draw an undirected edge. 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" ] -- ----------------------------------------------------------------------------- -- | Only when @mode == 'IpSep'@. 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" -- ----------------------------------------------------------------------------- -- | Either a 'Double' or a (2D) 'Point' (i.e. created with -- 'createPoint'). -- -- Whilst it is possible to create a 'Point' value with either a -- third co-ordinate or a forced position, these are ignored for -- printing/parsing. -- -- An optional prefix of @\'+\'@ is allowed when parsing. 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 -- A `+' would need to be quoted. `onFail` fmap DVal (parseSignedFloat False) -- Don't use parseUnqt! -- ----------------------------------------------------------------------------- -- | The mapping used for 'FontName' values in SVG output. -- -- More information can be found at . data SVGFontNames = SvgNames -- ^ Use the legal generic SVG font names. | PostScriptNames -- ^ Use PostScript font names. | FontConfigNames -- ^ Use fontconfig font conventions. 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 -- ----------------------------------------------------------------------------- -- | Maximum width and height of drawing in inches. data GraphSize = GSize { width :: Double -- | If @Nothing@, then the height is the -- same as the width. , height :: Maybe Double -- | If drawing is smaller than specified -- size, this value determines whether it -- is scaled up. , 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) (parseSignedFloat False) -- ----------------------------------------------------------------------------- -- | For 'Neato' unless indicated otherwise. data ModeType = Major | KK | Hier | IpSep | SpringMode -- ^ For 'Sfdp', requires Graphviz >= 2.32.0. | MaxEnt -- ^ For 'Sfdp', requires Graphviz >= 2.32.0. 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" unqtDot SpringMode = text "spring" unqtDot MaxEnt = text "maxent" instance ParseDot ModeType where parseUnqt = oneOf [ stringRep Major "major" , stringRep KK "KK" , stringRep Hier "hier" , stringRep IpSep "ipsep" , stringRep SpringMode "spring" , stringRep MaxEnt "maxent" ] -- ----------------------------------------------------------------------------- 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 -- ^ If 'PlainText' is used, the -- 'Html.Label' value is the entire -- \"shape\"; if anything else -- except 'PointShape' is used then -- the 'Html.Label' is embedded -- within the shape. | RecordLabel RecordFields -- ^ For nodes only; requires -- either 'Record' or -- 'MRecord' as the shape. 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 -- Don't have to worry about being able to tell the difference -- between an HtmlLabel and a RecordLabel starting with a PortPos, -- since the latter will be in quotes and the former won't. parseUnqt = oneOf [ HtmlLabel <$> parseAngled parseUnqt , RecordLabel <$> parseUnqt , StrLabel <$> parseUnqt ] parse = oneOf [ HtmlLabel <$> parseAngled parse , RecordLabel <$> parse , StrLabel <$> parse ] -- ----------------------------------------------------------------------------- -- | A RecordFields value should never be empty. type RecordFields = [RecordField] -- | Specifies the sub-values of a record-based label. By default, -- the cells are laid out horizontally; use 'FlipFields' to change -- the orientation of the fields (can be applied recursively). To -- change the default orientation, use 'RankDir'. data RecordField = LabelledTarget PortName EscString | PortName PortName -- ^ Will result in no label for -- that cell. | FieldLabel EscString | FlipFields RecordFields deriving (Eq, Ord, Show, Read) instance PrintDot RecordField where -- Have to use 'printPortName' to add the @\'<\'@ and @\'>\'@. 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 '|') -- Note: a singleton unquoted 'FieldLabel' is /not/ valid, as it -- will cause parsing problems for other 'Label' types. 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 -- | Print a 'PortName' value as expected within a Record data -- structure. printPortName :: PortName -> DotCode printPortName = angled . unqtRecordString . portName parseRecord :: Parse Text parseRecord = parseEscaped False recordEscChars [] unqtRecordString :: Text -> DotCode unqtRecordString = unqtEscaped recordEscChars recordEscChars :: [Char] recordEscChars = ['{', '}', '|', ' ', '<', '>'] -- ----------------------------------------------------------------------------- -- | How to treat a node whose name is of the form \"@|edgelabel|*@\" -- as a special node representing an edge label. data LabelScheme = NotEdgeLabel -- ^ No effect | CloseToCenter -- ^ Make node close to center of neighbor | CloseToOldCenter -- ^ Make node close to old center of neighbor | RemoveAndStraighten -- ^ Use a two-step process. 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 -- Use string-based parsing rather than parsing an integer just to make it easier parseUnqt = stringValue [ ("0", NotEdgeLabel) , ("1", CloseToCenter) , ("2", CloseToOldCenter) , ("3", RemoveAndStraighten) ] -- ----------------------------------------------------------------------------- data Point = Point { xCoord :: Double , yCoord :: Double -- | Can only be 'Just' for @'Dim' 3@ or greater. , zCoord :: Maybe Double -- | Input to Graphviz only: specify that the -- node position should not change. , forcePos :: Bool } deriving (Eq, Ord, Show, Read) -- | Create a point with only @x@ and @y@ values. 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 -- ----------------------------------------------------------------------------- -- | How to deal with node overlaps. -- -- Defaults to 'KeepOverlaps' /except/ for 'Fdp' and 'Sfdp'. -- -- The ability to specify the number of tries for 'Fdp''s initial -- force-directed technique is /not/ supported (by default, 'Fdp' uses -- @9@ passes of its in-built technique, and then @'PrismOverlap' -- Nothing@). -- -- For 'Sfdp', the default is @'PrismOverlap' (Just 0)@. data Overlap = KeepOverlaps | ScaleOverlaps -- ^ Remove overlaps by uniformly scaling in x and y. | ScaleXYOverlaps -- ^ Remove overlaps by separately scaling x and y. | PrismOverlap (Maybe Word16) -- ^ Requires the Prism -- library to be -- available (if not, -- this is equivalent to -- 'VoronoiOverlap'). @'Nothing'@ -- is equivalent to -- @'Just' 1000@. -- Influenced by -- 'OverlapScaling'. | VoronoiOverlap -- ^ Requires Graphviz >= 2.30.0. | CompressOverlap -- ^ Scale layout down as much as -- possible without introducing -- overlaps, assuming none to begin -- with. | VpscOverlap -- ^ Uses quadratic optimization to -- minimize node displacement. | IpsepOverlap -- ^ Only when @mode == 'IpSep'@ 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" -- | Note that @overlap=false@ defaults to @'PrismOverlap' Nothing@, -- but if the Prism library isn't available then it is equivalent to -- 'VoronoiOverlap'. 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 () -- | You should not have any layer separator characters for the -- 'LRName' option, as they won't be parseable. data LayerID = AllLayers | LRInt Int | LRName Text -- ^ Should not be a number or @"all"@. 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 -- Other two don't need quotes toDot li = unqtDot li unqtListToDot ll = do ls <- getLayerSep let s = unqtDot $ head ls hcat . punctuate s $ mapM unqtDot ll listToDot [l] = toDot l -- Might not need quotes, but probably will. Can't tell either -- way since we don't know what the separator character will be. listToDot ll = dquotes $ unqtDot ll instance ParseDot LayerID where parseUnqt = checkLayerName <$> parseLayerName -- tests for Int and All parse = oneOf [ checkLayerName <$> parseLayerName' , LRInt <$> parse -- Mainly for unquoted case. ] checkLayerName :: Text -> LayerID checkLayerName str = maybe checkAll LRInt $ stringToInt str where checkAll = if T.toLower str == "all" then AllLayers else LRName str -- Remember: this /must/ be a newtype as we can't use arbitrary -- LayerID values! -- | A list of layer names. The names should all be unique 'LRName' -- values, and when printed will use an arbitrary character from -- 'defLayerSep'. The values in the list are implicitly numbered -- @1, 2, ...@. 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 -- ^ Draw outgoing edges in order specified. | InEdges -- ^ Draw incoming edges in order specified. 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 -- ^ If non-negative, then packs; otherwise doesn't. 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 -- What happens if it parses 0? It's non-negative, but parses as False parseUnqt = oneOf [ PackMargin <$> parseUnqt , bool DontPack DoPack <$> onlyBool ] -- ----------------------------------------------------------------------------- data PackMode = PackNode | PackClust | PackGraph | PackArray Bool Bool (Maybe Int) -- ^ Sort by cols, sort -- by user, number of -- rows/cols 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 -- Also checks and removes quote characters 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 -- Have to be careful with this: if we try to parse points first, -- then a spline with no start and end points will erroneously get -- parsed as a point and then the parser will crash as it expects a -- closing quote character... parseUnqt = do splns <- parseUnqt case splns of [Spline Nothing Nothing [p]] -> return $ PointPos p _ -> return $ SplinePos splns parse = quotedParse parseUnqt -- ----------------------------------------------------------------------------- -- | Controls how (and if) edges are represented. -- -- For 'Dot', the default is 'SplineEdges'; for all other layouts -- the default is 'LineEdges'. data EdgeType = SplineEdges -- ^ Except for 'Dot', requires -- non-overlapping nodes (see -- 'Overlap'). | LineEdges | NoEdges | PolyLine | Ortho -- ^ Does not handle ports or edge labels in 'Dot'. | Curved -- ^ Requires Graphviz >= 2.30.0. | CompoundEdge -- ^ 'Fdp' only 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 -- Can't parse NoEdges without quotes. 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 -- ----------------------------------------------------------------------------- -- | Upper-case first character is major order; -- lower-case second character is minor order. 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) ] -- ----------------------------------------------------------------------------- -- | The number of points in the list must be equivalent to 1 mod 3; -- note that this is not checked. 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 -- Have to take into account the slightly different interpretation -- of Bool used as an option for parsing QuadType parseUnqt = oneOf [ stringRep NormalQT "normal" , stringRep FastQT "fast" , stringRep NoQT "none" , character '2' *> return FastQT -- weird bool , bool NoQT NormalQT <$> parse ] -- ----------------------------------------------------------------------------- -- | Specify the root node either as a Node attribute or a Graph attribute. data Root = IsCentral -- ^ For Nodes only | NotCentral -- ^ For Nodes only | NodeName Text -- ^ For Graphs only 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" ] -- ----------------------------------------------------------------------------- -- | Geometries of shapes are affected by the attributes 'Regular', -- 'Peripheries' and 'Orientation'. data Shape = BoxShape -- ^ Has synonyms of /rect/ and /rectangle/. | Polygon -- ^ Also affected by 'Sides', 'Skew' and 'Distortion'. | Ellipse -- ^ Has synonym of /oval/. | Circle | PointShape -- ^ Only affected by 'Peripheries', 'Width' and -- 'Height'. | Egg | Triangle | PlainText -- ^ Has synonym of /none/. Recommended for -- 'HtmlLabel's. | DiamondShape | Trapezium | Parallelogram | House | Pentagon | Hexagon | Septagon | Octagon | DoubleCircle | DoubleOctagon | TripleOctagon | InvTriangle | InvTrapezium | InvHouse | MDiamond | MSquare | MCircle | Square | Star -- ^ Requires Graphviz >= 2.32.0. | Underline -- ^ Requires Graphviz >= 2.36.0. | Note | Tab | Folder | Box3D | Component | Promoter -- ^ Requires Graphviz >= 2.30.0. | CDS -- ^ Requires Graphviz >= 2.30.0. | Terminator -- ^ Requires Graphviz >= 2.30.0. | UTR -- ^ Requires Graphviz >= 2.30.0. | PrimerSite -- ^ Requires Graphviz >= 2.30.0. | RestrictionSite -- ^ Requires Graphviz >= 2.30.0. | FivePovOverhang -- ^ Requires Graphviz >= 2.30.0. | ThreePovOverhang -- ^ Requires Graphviz >= 2.30.0. | NoOverhang -- ^ Requires Graphviz >= 2.30.0. | Assembly -- ^ Requires Graphviz >= 2.30.0. | Signature -- ^ Requires Graphviz >= 2.30.0. | Insulator -- ^ Requires Graphviz >= 2.30.0. | Ribosite -- ^ Requires Graphviz >= 2.30.0. | RNAStab -- ^ Requires Graphviz >= 2.30.0. | ProteaseSite -- ^ Requires Graphviz >= 2.30.0. | ProteinStab -- ^ Requires Graphviz >= 2.30.0. | RPromoter -- ^ Requires Graphviz >= 2.30.0. | RArrow -- ^ Requires Graphviz >= 2.30.0. | LArrow -- ^ Requires Graphviz >= 2.30.0. | LPromoter -- ^ Requires Graphviz >= 2.30.0. | Record -- ^ Must specify the record shape with a 'Label'. | MRecord -- ^ Must specify the record shape with a 'Label'. 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 Square = text "square" unqtDot Star = text "star" unqtDot Underline = text "underline" 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) , ("square", Square) , ("star", Star) , ("underline", Underline) , ("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" ] -- ----------------------------------------------------------------------------- -- | An individual style item. Except for 'DD', the @['String']@ -- should be empty. 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 (wrapWhitespace parseComma) parseList = quotedParse parseUnqtList `onFail` -- Might not necessarily need to be quoted if a singleton... fmap return parse parseArgs :: Parse [Text] parseArgs = bracketSep (character '(') parseComma (character ')') parseStyleName data StyleName = Dashed -- ^ Nodes and Edges | Dotted -- ^ Nodes and Edges | Solid -- ^ Nodes and Edges | Bold -- ^ Nodes and Edges | Invisible -- ^ Nodes and Edges | Filled -- ^ Nodes and Clusters | Striped -- ^ Rectangularly-shaped Nodes and -- Clusters; requires Graphviz >= 2.30.0 | Wedged -- ^ Elliptically-shaped Nodes only; -- requires Graphviz >= 2.30.0 | Diagonals -- ^ Nodes only | Rounded -- ^ Nodes and Clusters | Tapered -- ^ Edges only; requires Graphviz >= -- 2.29.0 | Radial -- ^ Nodes, Clusters and Graphs, for use -- with 'GradientAngle'; requires -- Graphviz >= 2.29.0 | DD Text -- ^ Device Dependent 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, '(', ')', ','] -- Used because the first character has slightly stricter requirements than the rest. 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 -- | For use with 'ViewPort'. 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 -- ^ Only valid for Nodes. | 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 [ stringReps VTop ["top", "t"] , stringReps VCenter ["centre", "center", "c"] , stringReps VBottom ["bottom", "b"] ] -- ----------------------------------------------------------------------------- -- | A list of search paths. 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 [ stringReps JLeft ["left", "l"] , stringReps JRight ["right", "r"] , stringReps JCenter ["center", "centre", "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" toDot (AspectRatio r) = toDot r toDot r = unqtDot r instance ParseDot Ratios where parseUnqt = parseRatio True parse = quotedParse parseUnqt <|> parseRatio False parseRatio :: Bool -> Parse Ratios parseRatio q = oneOf [ AspectRatio <$> parseSignedFloat q , stringRep FillRatio "fill" , stringRep CompressRatio "compress" , stringRep ExpandRatio "expand" , stringRep AutoRatio "auto" ] -- ----------------------------------------------------------------------------- -- | A numeric type with an explicit separation between integers and -- floating-point values. data Number = Int Int | Dbl Double deriving (Eq, Ord, Show, Read) instance PrintDot Number where unqtDot (Int i) = unqtDot i unqtDot (Dbl d) = unqtDot d toDot (Int i) = toDot i toDot (Dbl d) = toDot d instance ParseDot Number where parseUnqt = parseNumber True parse = quotedParse parseUnqt <|> parseNumber False parseNumber :: Bool -> Parse Number parseNumber q = Dbl <$> parseStrictFloat q <|> Int <$> parseUnqt -- ----------------------------------------------------------------------------- -- | If set, normalizes coordinates such that the first point is at -- the origin and the first edge is at the angle if specified. data Normalized = IsNormalized -- ^ Equivalent to @'NormalizedAngle' 0@. | NotNormalized | NormalizedAngle Double -- ^ Angle of first edge when -- normalized. Requires -- Graphviz >= 2.32.0. deriving (Eq, Ord, Show, Read) instance PrintDot Normalized where unqtDot IsNormalized = unqtDot True unqtDot NotNormalized = unqtDot False unqtDot (NormalizedAngle a) = unqtDot a toDot (NormalizedAngle a) = toDot a toDot norm = unqtDot norm instance ParseDot Normalized where parseUnqt = parseNormalized True parse = quotedParse parseUnqt <|> parseNormalized False parseNormalized :: Bool -> Parse Normalized parseNormalized q = NormalizedAngle <$> parseSignedFloat q <|> bool NotNormalized IsNormalized <$> onlyBool -- ----------------------------------------------------------------------------- -- | Determine how the 'Width' and 'Height' attributes specify the -- size of nodes. data NodeSize = GrowAsNeeded -- ^ Nodes will be the smallest width and height -- needed to contain the label and any possible -- image. 'Width' and 'Height' are the minimum -- allowed sizes. | SetNodeSize -- ^ 'Width' and 'Height' dictate the size of the node -- with a warning if the label cannot fit in this. | SetShapeSize -- ^ 'Width' and 'Height' dictate the size of the -- shape only and the label can expand out of the -- shape (with a warning). Requires Graphviz >= -- 2.38.0. deriving (Eq, Ord, Bounded, Enum, Show, Read) instance PrintDot NodeSize where unqtDot GrowAsNeeded = unqtDot False unqtDot SetNodeSize = unqtDot True unqtDot SetShapeSize = text "shape" instance ParseDot NodeSize where parseUnqt = bool GrowAsNeeded SetNodeSize <$> parseUnqt <|> stringRep SetShapeSize "shape" -- ----------------------------------------------------------------------------- {- As of Graphviz 2.36.0 this was commented out; as such it might come back, so leave this here in case we need it again. 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 -} graphviz-2999.20.2.0/Data/GraphViz/Commands/Available.hs0000644000000000000000000000521314535166704020622 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Commands.Available Description : Available command-line programs Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com These are the known programs that read in Dot graphs. -} module Data.GraphViz.Commands.Available where import Data.GraphViz.Parsing import Data.GraphViz.Printing -- ----------------------------------------------------------------------------- -- | The available Graphviz commands. The following directions are -- based upon those in the Graphviz man page (available online at -- , or if installed on your -- system @man graphviz@). Note that any command can be used on -- both directed and undirected graphs. -- -- When used with the 'Layout' attribute, it overrides any actual -- command called on the dot graph. data GraphvizCommand = Dot -- ^ For hierachical graphs (ideal for -- directed graphs). | Neato -- ^ For symmetric layouts of graphs -- (ideal for undirected graphs). | TwoPi -- ^ For radial layout of graphs. | Circo -- ^ For circular layout of graphs. | Fdp -- ^ Spring-model approach for -- undirected graphs. | Sfdp -- ^ As with Fdp, but ideal for large -- graphs. | Osage -- ^ Filter for drawing clustered graphs, -- requires Graphviz >= 2.28.0. | Patchwork -- ^ Draw clustered graphs as treemaps, -- requires Graphviz >= 2.28.0. 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) ] graphviz-2999.20.2.0/Data/GraphViz/Types/State.hs0000644000000000000000000002122214535166704017363 0ustar0000000000000000{-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Types.State Description : Create lookups for 'Attribute's. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module provides functions to assist with building 'Attribute' lookups. -} module Data.GraphViz.Types.State ( Path , recursiveCall -- , GraphState , ClusterLookup , getGraphInfo , addSubGraph , addGraphGlobals -- , NodeState , NodeLookup , getNodeLookup , toDotNodes , addNodeGlobals , addNode , addEdgeNodes -- , EdgeState , getDotEdges , addEdgeGlobals , addEdge ) where import Data.GraphViz.Attributes.Complete (Attributes, usedByClusters, usedByGraphs) import Data.GraphViz.Attributes.Same import Data.GraphViz.Types.Internal.Common import Control.Arrow ((&&&), (***)) import Control.Monad (when) import Control.Monad.State (State, execState, gets, modify) import Data.DList (DList) import qualified Data.DList as DList import Data.Function (on) import Data.Map (Map) import qualified Data.Map as Map import Data.Sequence (Seq, ViewL(..), (|>)) import qualified Data.Sequence as Seq import qualified Data.Set as Set -- ----------------------------------------------------------------------------- type GVState s a = State (StateValue s) a data StateValue a = SV { globalAttrs :: SAttrs , useGlobals :: Bool , globalPath :: Path , value :: a } deriving (Eq, Ord, Show, Read) -- | The path of clusters that must be traversed to reach this spot. type Path = Seq (Maybe GraphID) modifyGlobal :: (SAttrs -> SAttrs) -> GVState s () modifyGlobal f = modify f' where f' sv@(SV{globalAttrs = gas}) = sv{globalAttrs = f gas} modifyValue :: (s -> s) -> GVState s () modifyValue f = modify f' where f' sv@(SV{value = s}) = sv{value = f s} addGlobals :: Attributes -> GVState s () addGlobals as = do addG <- gets useGlobals when addG $ modifyGlobal (`unionWith` as) getGlobals :: GVState s SAttrs getGlobals = gets globalAttrs getPath :: GVState s Path getPath = gets globalPath modifyPath :: (Path -> Path) -> GVState s () modifyPath f = modify f' where f' sv@(SV{globalPath = p}) = sv{globalPath = f p} -- When calling recursively, back-up and restore the global attrs -- since they shouldn't change. -- -- Outer Maybe: Nothing for subgraphs, Just for clusters recursiveCall :: Maybe (Maybe GraphID) -> GVState s () -> GVState s () recursiveCall mc s = do gas <- getGlobals p <- getPath maybe (return ()) (modifyPath . flip (|>)) mc s modifyGlobal (const gas) modifyPath (const p) unionWith :: SAttrs -> Attributes -> SAttrs unionWith sas as = toSAttr as `Set.union` sas -- ----------------------------------------------------------------------------- -- Dealing with sub-graphs type GraphState a = GVState ClusterLookup' a -- | The available information for each cluster; the @['Path']@ -- denotes all locations where that particular cluster is located -- (more than one location can indicate possible problems). type ClusterLookup = Map (Maybe GraphID) ([Path], GlobalAttributes) type ClusterLookup' = Map (Maybe GraphID) ClusterInfo type ClusterInfo = (DList Path, SAttrs) getGraphInfo :: GraphState a -> (GlobalAttributes, ClusterLookup) getGraphInfo = ((graphGlobal . globalAttrs) &&& (convert . value)) . (`execState` initState) where convert = Map.map ((uniq . DList.toList) *** toGlobal) toGlobal = GraphAttrs . filter usedByClusters . unSame graphGlobal = GraphAttrs . filter usedByGraphs . unSame initState = SV Set.empty True Seq.empty Map.empty uniq = Set.toList . Set.fromList mergeCInfos :: ClusterInfo -> ClusterInfo -> ClusterInfo mergeCInfos (p1,as1) = DList.append p1 *** Set.union as1 addCluster :: Maybe (Maybe GraphID) -> Path -> SAttrs -> GraphState () addCluster Nothing _ _ = return () addCluster (Just gid) p as = modifyValue $ Map.insertWith mergeCInfos gid ci where ci = (DList.singleton p, as) -- Use this instead of recursiveCall addSubGraph :: Maybe (Maybe GraphID) -> GraphState a -> GraphState () addSubGraph mid cntns = do pth <- getPath -- Want path before we add it... recursiveCall mid $ do cntns -- But want attrs after we -- finish it. gas <- getGlobals addCluster mid pth gas addGraphGlobals :: GlobalAttributes -> GraphState () addGraphGlobals (GraphAttrs as) = addGlobals as addGraphGlobals _ = return () -- ----------------------------------------------------------------------------- -- Dealing with DotNodes -- | The available information on each 'DotNode' (both explicit and implicit). type NodeLookup n = Map n (Path, Attributes) type NodeLookup' n = Map n NodeInfo data NodeInfo = NI { atts :: SAttrs , gAtts :: SAttrs -- from globals , location :: Path } deriving (Eq, Ord, Show, Read) type NodeState n a = GVState (NodeLookup' n) a toDotNodes :: NodeLookup n -> [DotNode n] toDotNodes = map (\(n,(_,as)) -> DotNode n as) . Map.assocs getNodeLookup :: Bool -> NodeState n a -> NodeLookup n getNodeLookup addGs = Map.map combine . value . (`execState` initState) where initState = SV Set.empty addGs Seq.empty Map.empty combine ni = (location ni, unSame $ atts ni `Set.union` gAtts ni) -- New -> Old -> Inserted -- -- For specific attributes, newer one takes precedence; for global -- attributes and path, older one takes precedence. mergeNInfos :: NodeInfo -> NodeInfo -> NodeInfo mergeNInfos (NI a1 ga1 p1) (NI a2 ga2 p2) = NI (a1 `Set.union` a2) -- old one takes precendence (ga2 `Set.union` ga1) -- old one takes precendence (mergePs p2 p1) -- | If one 'Path' is a prefix of another, then take the longer one; -- otherwise, take the first 'Path'. mergePs :: Path -> Path -> Path mergePs p1 p2 = mrg' p1 p2 where mrg' = mrg `on` Seq.viewl mrg EmptyL _ = p2 mrg _ EmptyL = p1 mrg (c1 :< p1') (c2 :< p2') | c1 == c2 = mrg' p1' p2' | otherwise = p1 addNodeGlobals :: GlobalAttributes -> NodeState n () addNodeGlobals (NodeAttrs as) = addGlobals as addNodeGlobals _ = return () mergeNode :: (Ord n) => n -> Attributes -> SAttrs -> Path -> NodeState n () mergeNode n as gas p = modifyValue $ Map.insertWith mergeNInfos n ni where ni = NI (toSAttr as) gas p addNode :: (Ord n) => DotNode n -> NodeState n () addNode (DotNode n as) = do gas <- getGlobals p <- getPath -- insertWith takes func (new -> old -> inserted) mergeNode n as gas p addEdgeNodes :: (Ord n) => DotEdge n -> NodeState n () addEdgeNodes (DotEdge f t _) = do gas <- getGlobals p <- getPath addEN f gas p addEN t gas p where addEN n = mergeNode n [] -- ----------------------------------------------------------------------------- -- Dealing with DotEdges type EdgeState n a = GVState (DList (DotEdge n)) a getDotEdges :: Bool -> EdgeState n a -> [DotEdge n] getDotEdges addGs = DList.toList . value . (`execState` initState) where initState = SV Set.empty addGs Seq.empty DList.empty addEdgeGlobals :: GlobalAttributes -> EdgeState n () addEdgeGlobals (EdgeAttrs as) = addGlobals as addEdgeGlobals _ = return () addEdge :: DotEdge n -> EdgeState n () addEdge de@DotEdge{edgeAttributes = as} = do gas <- getGlobals let de' = de { edgeAttributes = unSame $ unionWith gas as } modifyValue $ (`DList.snoc` de') graphviz-2999.20.2.0/utils/TestParsing.hs0000755000000000000000000001133014535166704016201 0ustar0000000000000000{-# LANGUAGE MultiParamTypeClasses, OverloadedStrings #-} {- | Module : TestParsing Description : Check if the graphviz parser can parse "real world" Dot code. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module defines a program that determines if the provided files containing Dot code can be properly parsed using graphviz's parsers (with the assumption that the provided code is valid). -} module Main (main) where import Data.GraphViz import Data.GraphViz.Commands.IO (toUTF8) import Data.GraphViz.Exception import Data.GraphViz.Parsing (runParser) import Data.GraphViz.PreProcessing (preProcess) import qualified Data.GraphViz.Types.Generalised as G import Control.Exception (SomeException, evaluate, try) import Control.Monad (filterM, liftM) import qualified Data.ByteString.Lazy as B import Data.Either (either) import Data.Monoid (mappend) import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T import System.Directory import System.Environment (getArgs) import System.FilePath -- ----------------------------------------------------------------------------- main :: IO () main = tryParsing =<< getArgs where tryParsing [] = putStrLn "Test that the graphviz library can parse\ \ \"real life\" Dot code by passing a list\n\ \of files in which contain Dot graphs.\n\ \\n\ \One way of using this file:\n\t\ \$ locate -r \".*\\.\\(gv\\|dot\\)$\" -0\ \ | xargs -0 TestParsing.hs" tryParsing [fp] = do isDir <- doesDirectoryExist fp if isDir then mapM_ tryParseFile =<< getDContents fp else tryParseFile fp tryParsing fs = mapM_ tryParseFile fs getDContents :: FilePath -> IO [FilePath] getDContents fp = (filterM doesFileExist . map (fp )) =<< getDirectoryContents fp -- ----------------------------------------------------------------------------- withParse :: (Show a, PPDotRepr dg n) => (a -> IO Text) -> (dg n -> IO ()) -> (ErrMsg -> String) -> a -> IO () withParse toStr withDG cmbErr a = do dc <- liftM getMsg . try $ toStr a case dc of Right dc' -> do edg <- tryParse dc' case edg of (Right dg) -> withDG dg (Left err) -> do putStr (show a) putStrLn " - Parsing problem!" putStrLn $ cmbErr err putStrLn "" Left err -> do putStr (show a) putStrLn " - IO problem!" putStrLn err putStrLn "" where getMsg :: Either SomeException Text -> Either ErrMsg Text getMsg = either (Left . show) Right type GDG = G.DotGraph Text type ErrMsg = String tryParseFile :: FilePath -> IO () tryParseFile fp = withParse readUTF8File ((`seq` return ()) . T.length . printDotGraph . asGDG) ("Cannot parse as a G.DotGraph: "++) fp where asGDG :: GDG -> GDG asGDG = id tryParse :: (PPDotRepr dg n) => Text -> IO (Either ErrMsg (dg n)) tryParse dc = handle getErr $ let (dg, rst) = runParser parse $ preProcess dc in T.length rst `seq` return (eitherLR (augmentErr rst) id dg) where getErr :: SomeException -> IO (Either ErrMsg a) getErr = return . Left . show augmentErr rst err = err ++ "\n\tRemaining input: " ++ show res where sampleLen = 35 res | T.length rst <= sampleLen = rst | otherwise = T.take sampleLen rst `mappend` " ..." eitherLR f g = either (Left . f) (Right . g) -- Force any encoding errors into the IO section rather than when parsing. readUTF8File :: FilePath -> IO Text readUTF8File fp = do cnts <- liftM toUTF8 $ B.readFile fp _ <- evaluate $ T.length cnts return cnts graphviz-2999.20.2.0/tests/Main.hs0000644000000000000000000000115214535166704014622 0ustar0000000000000000{- | Module : Main Description : Top-level HSpec runner Copyright : Matthew Sackman, Ivan Lazar Miljenovic License : BSD3 Maintainer : Ivan.Miljenovic@gmail.com Used as we want to wrap default QuickCheck configurations. -} module Main where import qualified Spec import Test.Hspec.QuickCheck (modifyMaxSize, modifyMaxSuccess) import Test.Hspec.Runner (hspec) -------------------------------------------------------------------------------- main :: IO () main = hspec . modifyMaxSuccess (const 200) . modifyMaxSize (const 50) $ Spec.spec graphviz-2999.20.2.0/tests/Data/GraphViz/Testing/Instances.hs0000644000000000000000000000173114535166704021710 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE OverloadedStrings #-} {- | Module : Data.GraphViz.Testing.Instances Description : 'Arbitrary' instances for graphviz. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module exports the 'Arbitrary' instances for the various types used to represent Graphviz Dot code. Note that they do not generally generate /sensible/ values for the various types; in particular, there's no guarantee that the 'Attributes' chosen for a particular value type are indeed legal for that type. -} module Data.GraphViz.Testing.Instances() where import Data.Graph.Inductive.Arbitrary () import Data.GraphViz.Testing.Instances.Canonical () import Data.GraphViz.Testing.Instances.Generalised () import Data.GraphViz.Testing.Instances.Graph () -- ----------------------------------------------------------------------------- graphviz-2999.20.2.0/tests/Data/GraphViz/Testing/Properties.hs0000644000000000000000000002246114535166704022120 0ustar0000000000000000{-# LANGUAGE FlexibleContexts, MultiParamTypeClasses #-} {- | Module : Data.GraphViz.Testing.Properties Description : Properties for testing. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com Various properties that should hold true for the graphviz library. -} module Data.GraphViz.Testing.Properties where import Data.GraphViz (dotizeGraph, graphToDot, nonClusteredParams, setDirectedness) import Data.GraphViz.Algorithms import Data.GraphViz.Internal.Util (groupSortBy, isSingle) import Data.GraphViz.Parsing (ParseDot(..), parseIt, parseIt') import Data.GraphViz.PreProcessing (preProcess) import Data.GraphViz.Printing (PrintDot(..), printIt) import Data.GraphViz.Testing.Proxy (DGProxy(..)) import Data.GraphViz.Types (DotEdge(..), DotNode(..), DotRepr(..), GlobalAttributes(..), PrintDotRepr, edgeInformationClean, graphEdges, graphNodes, nodeInformationClean, printDotGraph) import Data.GraphViz.Types.Canonical (DotGraph(..), DotStatements(..)) import qualified Data.GraphViz.Types.Generalised as G import Test.QuickCheck import Control.Arrow ((&&&)) import Data.Function (on) import Data.Graph.Inductive (DynGraph, Graph, edges, emap, equal, labEdges, labNodes, nmap, nodes) import Data.List (nub, sort) import qualified Data.Map as Map import qualified Data.Set as Set import Data.Text.Lazy (Text) -- ----------------------------------------------------------------------------- -- The properties to test for -- | Checking that @parse . print == id@; that is, graphviz can parse -- its own output. prop_printParseID :: (ParseDot a, PrintDot a, Eq a) => a -> Bool prop_printParseID a = tryParse' a == a -- | A version of 'prop_printParse' specifically for lists; it ensures -- that the list is not empty (as most list-based parsers fail on -- empty lists). prop_printParseListID :: (ParseDot a, PrintDot a, Eq a) => [a] -> Property prop_printParseListID as = not (null as) ==> prop_printParseID as -- | When converting a canonical 'DotGraph' value to any other one, -- they should generate the same Dot code. prop_generalisedSameDot :: (Ord n, PrintDot n, ParseDot n) => DotGraph n -> Bool prop_generalisedSameDot dg = printDotGraph dg == printDotGraph gdg where gdg = canonicalToType (DGProxy :: DGProxy G.DotGraph) dg -- | Pre-processing shouldn't change the output of printed Dot code. -- This should work for all 'PrintDot' instances, but is more -- specific to 'DotGraph' values. prop_preProcessingID :: (PrintDotRepr dg n) => dg n -> Bool prop_preProcessingID dg = preProcess dotCode == dotCode where dotCode = printDotGraph dg -- | This property verifies that 'dotizeGraph', etc. only /augment/ the -- original graph; that is, the actual nodes, edges and labels for -- each remain unchanged. Whilst 'dotize', etc. only require -- 'Graph' instances, this property requires 'DynGraph' (which is a -- sub-class of 'Graph') instances to be able to strip off the -- 'Attributes' augmentations. prop_dotizeAugment :: (DynGraph g, Eq n, Ord e) => g n e -> Bool prop_dotizeAugment g = equal g (unAugment g') where g' = setDirectedness dotizeGraph nonClusteredParams g unAugment = nmap snd . emap snd -- | After augmentation, each node and edge should have a non-empty -- | list of 'Attributes'. prop_dotizeHasAugment :: (DynGraph g, Ord e) => g n e -> Bool prop_dotizeHasAugment g = all (not . null) nodeAugments && all (not . null) edgeAugments where g' = setDirectedness dotizeGraph nonClusteredParams g nodeAugments = map (fst . snd) $ labNodes g' edgeAugments = map (fst . \(_,_,l) -> l) $ labEdges g' -- | When a graph with multiple edges is augmented, then all edges -- should have unique 'Attributes' (namely the positions). Note -- that this may not hold true with custom supplied 'Attributes' -- (i.e. not using one of the @dotize@ functions). prop_dotizeAugmentUniq :: (DynGraph g, Ord e) => g n e -> Bool prop_dotizeAugmentUniq g = all uniqLs lss where g' = setDirectedness dotizeGraph nonClusteredParams g les = map (\(f,t,l) -> ((f,t),l)) $ labEdges g' lss = map (map snd) . filter (not . isSingle) $ groupSortBy fst les uniqLs [] = False -- Needs to have at least /one/ Attribute! uniqLs ls = ls == nub ls -- | Ensure that the definition of 'nodeInformation' for a DotRepr -- finds all the nodes. prop_findAllNodes :: (DotRepr dg Int, Ord el, Graph g) => DGProxy dg -> g nl el -> Bool prop_findAllNodes dgp g = ((==) `on` sort) gns dgns where gns = nodes g dg = canonicalToType dgp $ setDirectedness graphToDot nonClusteredParams g dgns = map nodeID $ graphNodes dg -- | Ensure that the definition of 'nodeInformation' for DotReprs -- finds all the nodes when the explicit 'DotNode' definitions are -- removed. prop_findAllNodesE :: (DotRepr dg Int, Ord el, Graph g) => DGProxy dg -> g nl el -> Bool prop_findAllNodesE dgp g = ((==) `on` sort) gns dgns where gns = nodes g dg = canonicalToType dgp . removeNodes $ setDirectedness graphToDot nonClusteredParams g dgns = map nodeID $ graphNodes dg removeNodes dot@DotGraph{graphStatements = stmts} = dot { graphStatements = stmts {nodeStmts = filter notInEdge $ nodeStmts stmts} } gnes = Set.fromList . concatMap (\(f,t) -> [f,t]) $ edges g notInEdge dn = nodeID dn `Set.notMember` gnes -- | Ensure that the definition of 'edgeInformation' for DotReprs -- finds all the nodes. prop_findAllEdges :: (DotRepr dg Int, Graph g) => DGProxy dg -> g nl el -> Bool prop_findAllEdges dgp g = ((==) `on` sort) ges dges where ges = edges g dg = canonicalToType dgp $ graphToDot nonClusteredParams g dges = map (fromNode &&& toNode) $ graphEdges dg -- | There should be no clusters or global attributes when converting -- a 'Graph' to a DotRepr (via fromCanonical) without any formatting -- or clustering. prop_noGraphInfo :: (DotRepr dg Int, Ord el, Graph g) => DGProxy dg -> g nl el -> Bool prop_noGraphInfo dgp g = info == (GraphAttrs [], Map.empty) where dg = canonicalToType dgp $ setDirectedness graphToDot nonClusteredParams g info = graphStructureInformation dg -- | Canonicalisation should be idempotent. prop_canonicalise :: (DotRepr dg n) => CanonicaliseOptions -> dg n -> Bool prop_canonicalise copts g = cdg == canonicaliseOptions copts cdg where cdg = canonicaliseOptions copts g -- | Canonicalisation shouldn't change any nodes. prop_canonicaliseNodes :: (DotRepr dg n) => CanonicaliseOptions -> dg n -> Bool prop_canonicaliseNodes copts g = nodeInformationClean True g == nodeInformationClean True cdg where cdg = canonicaliseOptions copts g -- | Canonicalisation shouldn't change any edges. prop_canonicaliseEdges :: (DotRepr dg n) => CanonicaliseOptions -> dg n -> Bool prop_canonicaliseEdges copts g = sort (edgeInformationClean True g) == sort (edgeInformationClean True cdg) where cdg = canonicaliseOptions copts g -- | Removing transitive edges should be idempotent. prop_transitive :: (DotRepr dg n) => CanonicaliseOptions -> dg n -> Bool prop_transitive copts g = tdg == transitiveReductionOptions copts tdg where tdg = transitiveReductionOptions copts g -- | Transitive reduction shouldn't change any nodes. prop_transitiveNodes :: (DotRepr dg n) => CanonicaliseOptions -> dg n -> Bool prop_transitiveNodes copts g = nodeInformationClean True g == nodeInformationClean True cdg where cdg = transitiveReductionOptions copts g -- ----------------------------------------------------------------------------- -- Helper utility functions -- | A utility function to use for debugging purposes for trying to -- find how graphviz /is/ parsing something. This is easier than -- using @'parseIt' . 'printIt'@ directly, since it avoids having to -- enter and explicit type signature. tryParse :: (ParseDot a, PrintDot a) => a -> (a, Text) tryParse = parseIt . printIt -- | Equivalent to 'tryParse' except that it is assumed that the -- entire 'String' *is* fully consumed. tryParse' :: (ParseDot a, PrintDot a) => a -> a tryParse' = parseIt' . printIt -- | A wrapper around 'fromCanonical' that lets you specify up-front -- what type to create (it need not be a sensible value). canonicalToType :: (DotRepr dg n) => DGProxy dg -> DotGraph n -> dg n canonicalToType _ = fromCanonical graphviz-2999.20.2.0/tests/Data/GraphViz/Testing/Instances/Helpers.hs0000644000000000000000000000766514535166704023326 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_HADDOCK hide #-} {-# LANGUAGE OverloadedStrings #-} {- | Module : Data.GraphViz.Testing.Instances.Helpers Description : Helper functions for graphviz Arbitrary instances. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Testing.Instances.Helpers where import Data.GraphViz.Internal.State (initialState, layerListSep, layerSep) import Data.GraphViz.Parsing (isNumString) import Test.QuickCheck import Control.Monad (liftM, liftM2) import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T -- ----------------------------------------------------------------------------- -- Helper Functions instance Arbitrary Text where arbitrary = arbText shrink = filter validString . map T.pack . nonEmptyShrinks' . T.unpack arbText :: Gen Text arbText = suchThat genStr notBool where genStr = liftM2 T.cons (elements notDigits) (liftM T.concat . listOf $ elements strChr) notDigits = ['a'..'z'] ++ ['\'', '"', ' ', '(', ')', ',', ':', '\\'] strChr = map T.singleton $ notDigits ++ '.' : ['0'..'9'] arbString :: Gen String arbString = liftM T.unpack arbitrary fromPositive :: Positive a -> a fromPositive (Positive a) = a posArbitrary :: (Arbitrary a, Num a, Ord a) => Gen a posArbitrary = liftM fromPositive arbitrary arbIDString :: Gen Text arbIDString = suchThat genStr notBool where genStr = liftM2 T.cons (elements frst) (liftM T.pack . listOf $ elements rest) frst = ['a'..'z'] ++ ['_'] rest = frst ++ ['0'.. '9'] validString :: Text -> Bool validString = liftM2 (&&) notBool notNumStr notBool :: Text -> Bool notBool "true" = False notBool "false" = False notBool _ = True shrinkString :: String -> [String] shrinkString = map T.unpack . shrink . T.pack notNumStr :: Text -> Bool notNumStr = not . isNumString True arbBounded :: (Bounded a, Enum a) => Gen a arbBounded = elements [minBound .. maxBound] arbLayerName :: Gen Text arbLayerName = suchThat arbitrary (T.all notLayerSep) where defLayerSep = layerSep initialState ++ layerListSep initialState notLayerSep = (`notElem` defLayerSep) arbStyleName :: Gen Text arbStyleName = suchThat arbitrary (T.all notBrackCom) where notBrackCom = flip notElem ['(', ')', ',', ' '] arbList :: (Arbitrary a) => Gen [a] arbList = listOf1 arbitrary nonEmptyShrinks :: (Arbitrary a) => [a] -> [[a]] nonEmptyShrinks = filter (not . null) . shrink nonEmptyShrinks' :: [a] -> [[a]] nonEmptyShrinks' = filter (not . null) . listShrink' -- Shrink lists with more than one value only by removing values, not -- by shrinking individual items. listShrink :: (Arbitrary a) => [a] -> [[a]] listShrink [a] = map return $ shrink a listShrink as = listShrink' as -- Just shrink the size. listShrink' :: [a] -> [[a]] listShrink' as = rm (length as) as where rm 0 _ = [] rm 1 _ = [[]] rm n xs = xs1 : xs2 : ( [ xs1' ++ xs2 | xs1' <- rm n1 xs1, not (null xs1') ] `ilv` [ xs1 ++ xs2' | xs2' <- rm n2 xs2, not (null xs2') ] ) where n1 = n `div` 2 xs1 = take n1 xs n2 = n - n1 xs2 = drop n1 xs [] `ilv` ys = ys xs `ilv` [] = xs (x:xs) `ilv` (y:ys) = x : y : (xs `ilv` ys) -- When a Maybe value is a sub-component, and we need shrink to return -- a value. shrinkM :: (Arbitrary a) => Maybe a -> [Maybe a] shrinkM Nothing = [Nothing] shrinkM j = shrink j shrinkL :: (Arbitrary a) => [a] -> [[a]] shrinkL xs = case listShrink xs of [] -> [xs] xs' -> xs' notInt :: Double -> Bool notInt d = fromIntegral (round d :: Int) /= d returnCheck :: (Eq a) => a -> a -> [a] returnCheck o n = if o == n then [] else [n] graphviz-2999.20.2.0/tests/Data/GraphViz/Testing/Instances/Attributes.hs0000644000000000000000000013012014535166704024031 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_HADDOCK hide #-} {-# LANGUAGE CPP, OverloadedStrings #-} {- | Module : Data.GraphViz.Testing.Instances.Attributes Description : Attribute instances for Arbitrary. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Testing.Instances.Attributes ( arbGraphAttrs , arbSubGraphAttrs , arbClusterAttrs , arbNodeAttrs , arbEdgeAttrs ) where import Data.GraphViz.Testing.Instances.Helpers import Data.GraphViz.Attributes.Colors.Brewer import Data.GraphViz.Attributes.Colors.SVG (SVGColor) import Data.GraphViz.Attributes.Colors.X11 (X11Color) import Data.GraphViz.Attributes.Complete import qualified Data.GraphViz.Attributes.HTML as Html import Data.GraphViz.Attributes.Internal (compassLookup) import Data.GraphViz.Internal.State (initialState, layerListSep, layerSep) import Data.GraphViz.Internal.Util (bool) import Test.QuickCheck import Control.Monad (liftM, liftM2, liftM3, liftM4) import Data.List (delete, groupBy, nub) import qualified Data.Map as Map import Data.Text.Lazy (Text) import qualified Data.Text.Lazy as T import System.FilePath (searchPathSeparator) #if !MIN_VERSION_QuickCheck(2,9,0) import Data.GraphViz.Internal.Util (createVersion) import Data.Version (Version(..)) #endif -- ----------------------------------------------------------------------------- -- Defining Arbitrary instances for Attributes arbGraphAttrs :: Gen Attributes arbGraphAttrs = arbAttrs usedByGraphs arbSubGraphAttrs :: Gen Attributes arbSubGraphAttrs = arbAttrs usedBySubGraphs arbClusterAttrs :: Gen Attributes arbClusterAttrs = arbAttrs usedByClusters arbNodeAttrs :: Gen Attributes arbNodeAttrs = arbAttrs usedByNodes arbEdgeAttrs :: Gen Attributes arbEdgeAttrs = arbAttrs usedByEdges arbAttrs :: (Attribute -> Bool) -> Gen Attributes arbAttrs p = liftM (filter p) arbList instance Arbitrary Attribute where arbitrary = oneof [ liftM Damping arbitrary , liftM K arbitrary , liftM URL arbitrary , liftM Area arbitrary , liftM ArrowHead arbitrary , liftM ArrowSize arbitrary , liftM ArrowTail arbitrary , liftM Background arbitrary , liftM BoundingBox arbitrary , liftM BgColor arbList , liftM Center arbitrary , liftM ClusterRank arbitrary , liftM Color arbList , liftM ColorScheme arbitrary , liftM Comment arbitrary , liftM Compound arbitrary , liftM Concentrate arbitrary , liftM Constraint arbitrary , liftM Decorate arbitrary , liftM DefaultDist arbitrary , liftM Dim arbitrary , liftM Dimen arbitrary , liftM Dir arbitrary , liftM DirEdgeConstraints arbitrary , liftM Distortion arbitrary , liftM DPI arbitrary , liftM EdgeURL arbitrary , liftM EdgeTarget arbitrary , liftM EdgeTooltip arbitrary , liftM Epsilon arbitrary , liftM ESep arbitrary , liftM FillColor arbList , liftM FixedSize arbitrary , liftM FontColor arbitrary , liftM FontName arbitrary , liftM FontNames arbitrary , liftM FontPath arbitrary , liftM FontSize arbitrary , liftM ForceLabels arbitrary , liftM GradientAngle arbitrary , liftM Group arbitrary , liftM HeadURL arbitrary , liftM Head_LP arbitrary , liftM HeadClip arbitrary , liftM HeadLabel arbitrary , liftM HeadPort arbitrary , liftM HeadTarget arbitrary , liftM HeadTooltip arbitrary , liftM Height arbitrary , liftM ID arbitrary , liftM Image arbitrary , liftM ImagePath arbitrary , liftM ImageScale arbitrary , liftM InputScale arbitrary , liftM Label arbitrary , liftM LabelURL arbitrary , liftM LabelScheme arbitrary , liftM LabelAngle arbitrary , liftM LabelDistance arbitrary , liftM LabelFloat arbitrary , liftM LabelFontColor arbitrary , liftM LabelFontName arbitrary , liftM LabelFontSize arbitrary , liftM LabelJust arbitrary , liftM LabelLoc arbitrary , liftM LabelTarget arbitrary , liftM LabelTooltip arbitrary , liftM Landscape arbitrary , liftM Layer arbitrary , liftM LayerListSep arbitrary , liftM Layers arbitrary , liftM LayerSelect arbitrary , liftM LayerSep arbitrary , liftM Layout arbitrary , liftM Len arbitrary , liftM Levels arbitrary , liftM LevelsGap arbitrary , liftM LHead arbitrary , liftM LHeight arbitrary , liftM LPos arbitrary , liftM LTail arbitrary , liftM LWidth arbitrary , liftM Margin arbitrary , liftM MaxIter arbitrary , liftM MCLimit arbitrary , liftM MinDist arbitrary , liftM MinLen arbitrary , liftM Mode arbitrary , liftM Model arbitrary , liftM Mosek arbitrary , liftM NodeSep arbitrary , liftM NoJustify arbitrary , liftM Normalize arbitrary , liftM NoTranslate arbitrary , liftM Nslimit arbitrary , liftM Nslimit1 arbitrary , liftM Ordering arbitrary , liftM Orientation arbitrary , liftM OutputOrder arbitrary , liftM Overlap arbitrary , liftM OverlapScaling arbitrary , liftM OverlapShrink arbitrary , liftM Pack arbitrary , liftM PackMode arbitrary , liftM Pad arbitrary , liftM Page arbitrary , liftM PageDir arbitrary , liftM PenColor arbitrary , liftM PenWidth arbitrary , liftM Peripheries arbitrary , liftM Pin arbitrary , liftM Pos arbitrary , liftM QuadTree arbitrary , liftM Quantum arbitrary , liftM Rank arbitrary , liftM RankDir arbitrary , liftM RankSep arbList , liftM Ratio arbitrary , liftM Rects arbList , liftM Regular arbitrary , liftM ReMinCross arbitrary , liftM RepulsiveForce arbitrary , liftM Root arbitrary , liftM Rotate arbitrary , liftM Rotation arbitrary , liftM SameHead arbitrary , liftM SameTail arbitrary , liftM SamplePoints arbitrary , liftM Scale arbitrary , liftM SearchSize arbitrary , liftM Sep arbitrary , liftM Shape arbitrary , liftM ShowBoxes arbitrary , liftM Sides arbitrary , liftM Size arbitrary , liftM Skew arbitrary , liftM Smoothing arbitrary , liftM SortV arbitrary , liftM Splines arbitrary , liftM Start arbitrary , liftM Style arbList , liftM StyleSheet arbitrary , liftM TailURL arbitrary , liftM Tail_LP arbitrary , liftM TailClip arbitrary , liftM TailLabel arbitrary , liftM TailPort arbitrary , liftM TailTarget arbitrary , liftM TailTooltip arbitrary , liftM Target arbitrary , liftM Tooltip arbitrary , liftM TrueColor arbitrary , liftM Vertices arbList , liftM ViewPort arbitrary , liftM VoroMargin arbitrary , liftM Weight arbitrary , liftM Width arbitrary , liftM XDotVersion arbitrary , liftM XLabel arbitrary , liftM XLP arbitrary , liftM2 UnknownAttribute (suchThat arbIDString validUnknown) arbitrary ] shrink (Damping v) = map Damping $ shrink v shrink (K v) = map K $ shrink v shrink (URL v) = map URL $ shrink v shrink (Area v) = map Area $ shrink v shrink (ArrowHead v) = map ArrowHead $ shrink v shrink (ArrowSize v) = map ArrowSize $ shrink v shrink (ArrowTail v) = map ArrowTail $ shrink v shrink (Background v) = map Background $ shrink v shrink (BoundingBox v) = map BoundingBox $ shrink v shrink (BgColor v) = map BgColor $ nonEmptyShrinks v shrink (Center v) = map Center $ shrink v shrink (ClusterRank v) = map ClusterRank $ shrink v shrink (Color v) = map Color $ nonEmptyShrinks v shrink (ColorScheme v) = map ColorScheme $ shrink v shrink (Comment v) = map Comment $ shrink v shrink (Compound v) = map Compound $ shrink v shrink (Concentrate v) = map Concentrate $ shrink v shrink (Constraint v) = map Constraint $ shrink v shrink (Decorate v) = map Decorate $ shrink v shrink (DefaultDist v) = map DefaultDist $ shrink v shrink (Dim v) = map Dim $ shrink v shrink (Dimen v) = map Dimen $ shrink v shrink (Dir v) = map Dir $ shrink v shrink (DirEdgeConstraints v) = map DirEdgeConstraints $ shrink v shrink (Distortion v) = map Distortion $ shrink v shrink (DPI v) = map DPI $ shrink v shrink (EdgeURL v) = map EdgeURL $ shrink v shrink (EdgeTarget v) = map EdgeTarget $ shrink v shrink (EdgeTooltip v) = map EdgeTooltip $ shrink v shrink (Epsilon v) = map Epsilon $ shrink v shrink (ESep v) = map ESep $ shrink v shrink (FillColor v) = map FillColor $ nonEmptyShrinks v shrink (FixedSize v) = map FixedSize $ shrink v shrink (FontColor v) = map FontColor $ shrink v shrink (FontName v) = map FontName $ shrink v shrink (FontNames v) = map FontNames $ shrink v shrink (FontPath v) = map FontPath $ shrink v shrink (FontSize v) = map FontSize $ shrink v shrink (ForceLabels v) = map ForceLabels $ shrink v shrink (GradientAngle v) = map GradientAngle $ shrink v shrink (Group v) = map Group $ shrink v shrink (HeadURL v) = map HeadURL $ shrink v shrink (Head_LP v) = map Head_LP $ shrink v shrink (HeadClip v) = map HeadClip $ shrink v shrink (HeadLabel v) = map HeadLabel $ shrink v shrink (HeadPort v) = map HeadPort $ shrink v shrink (HeadTarget v) = map HeadTarget $ shrink v shrink (HeadTooltip v) = map HeadTooltip $ shrink v shrink (Height v) = map Height $ shrink v shrink (ID v) = map ID $ shrink v shrink (Image v) = map Image $ shrink v shrink (ImagePath v) = map ImagePath $ shrink v shrink (ImageScale v) = map ImageScale $ shrink v shrink (InputScale v) = map InputScale $ shrink v shrink (Label v) = map Label $ shrink v shrink (LabelURL v) = map LabelURL $ shrink v shrink (LabelScheme v) = map LabelScheme $ shrink v shrink (LabelAngle v) = map LabelAngle $ shrink v shrink (LabelDistance v) = map LabelDistance $ shrink v shrink (LabelFloat v) = map LabelFloat $ shrink v shrink (LabelFontColor v) = map LabelFontColor $ shrink v shrink (LabelFontName v) = map LabelFontName $ shrink v shrink (LabelFontSize v) = map LabelFontSize $ shrink v shrink (LabelJust v) = map LabelJust $ shrink v shrink (LabelLoc v) = map LabelLoc $ shrink v shrink (LabelTarget v) = map LabelTarget $ shrink v shrink (LabelTooltip v) = map LabelTooltip $ shrink v shrink (Landscape v) = map Landscape $ shrink v shrink (Layer v) = map Layer $ shrink v shrink (LayerListSep v) = map LayerListSep $ shrink v shrink (Layers v) = map Layers $ shrink v shrink (LayerSelect v) = map LayerSelect $ shrink v shrink (LayerSep v) = map LayerSep $ shrink v shrink (Layout v) = map Layout $ shrink v shrink (Len v) = map Len $ shrink v shrink (Levels v) = map Levels $ shrink v shrink (LevelsGap v) = map LevelsGap $ shrink v shrink (LHead v) = map LHead $ shrink v shrink (LHeight v) = map LHeight $ shrink v shrink (LPos v) = map LPos $ shrink v shrink (LTail v) = map LTail $ shrink v shrink (LWidth v) = map LWidth $ shrink v shrink (Margin v) = map Margin $ shrink v shrink (MaxIter v) = map MaxIter $ shrink v shrink (MCLimit v) = map MCLimit $ shrink v shrink (MinDist v) = map MinDist $ shrink v shrink (MinLen v) = map MinLen $ shrink v shrink (Mode v) = map Mode $ shrink v shrink (Model v) = map Model $ shrink v shrink (Mosek v) = map Mosek $ shrink v shrink (NodeSep v) = map NodeSep $ shrink v shrink (NoJustify v) = map NoJustify $ shrink v shrink (Normalize v) = map Normalize $ shrink v shrink (NoTranslate v) = map NoTranslate $ shrink v shrink (Nslimit v) = map Nslimit $ shrink v shrink (Nslimit1 v) = map Nslimit1 $ shrink v shrink (Ordering v) = map Ordering $ shrink v shrink (Orientation v) = map Orientation $ shrink v shrink (OutputOrder v) = map OutputOrder $ shrink v shrink (Overlap v) = map Overlap $ shrink v shrink (OverlapScaling v) = map OverlapScaling $ shrink v shrink (OverlapShrink v) = map OverlapShrink $ shrink v shrink (Pack v) = map Pack $ shrink v shrink (PackMode v) = map PackMode $ shrink v shrink (Pad v) = map Pad $ shrink v shrink (Page v) = map Page $ shrink v shrink (PageDir v) = map PageDir $ shrink v shrink (PenColor v) = map PenColor $ shrink v shrink (PenWidth v) = map PenWidth $ shrink v shrink (Peripheries v) = map Peripheries $ shrink v shrink (Pin v) = map Pin $ shrink v shrink (Pos v) = map Pos $ shrink v shrink (QuadTree v) = map QuadTree $ shrink v shrink (Quantum v) = map Quantum $ shrink v shrink (Rank v) = map Rank $ shrink v shrink (RankDir v) = map RankDir $ shrink v shrink (RankSep v) = map RankSep $ nonEmptyShrinks v shrink (Ratio v) = map Ratio $ shrink v shrink (Rects v) = map Rects $ nonEmptyShrinks v shrink (Regular v) = map Regular $ shrink v shrink (ReMinCross v) = map ReMinCross $ shrink v shrink (RepulsiveForce v) = map RepulsiveForce $ shrink v shrink (Root v) = map Root $ shrink v shrink (Rotate v) = map Rotate $ shrink v shrink (Rotation v) = map Rotation $ shrink v shrink (SameHead v) = map SameHead $ shrink v shrink (SameTail v) = map SameTail $ shrink v shrink (SamplePoints v) = map SamplePoints $ shrink v shrink (Scale v) = map Scale $ shrink v shrink (SearchSize v) = map SearchSize $ shrink v shrink (Sep v) = map Sep $ shrink v shrink (Shape v) = map Shape $ shrink v shrink (ShowBoxes v) = map ShowBoxes $ shrink v shrink (Sides v) = map Sides $ shrink v shrink (Size v) = map Size $ shrink v shrink (Skew v) = map Skew $ shrink v shrink (Smoothing v) = map Smoothing $ shrink v shrink (SortV v) = map SortV $ shrink v shrink (Splines v) = map Splines $ shrink v shrink (Start v) = map Start $ shrink v shrink (Style v) = map Style $ nonEmptyShrinks v shrink (StyleSheet v) = map StyleSheet $ shrink v shrink (TailURL v) = map TailURL $ shrink v shrink (Tail_LP v) = map Tail_LP $ shrink v shrink (TailClip v) = map TailClip $ shrink v shrink (TailLabel v) = map TailLabel $ shrink v shrink (TailPort v) = map TailPort $ shrink v shrink (TailTarget v) = map TailTarget $ shrink v shrink (TailTooltip v) = map TailTooltip $ shrink v shrink (Target v) = map Target $ shrink v shrink (Tooltip v) = map Tooltip $ shrink v shrink (TrueColor v) = map TrueColor $ shrink v shrink (Vertices v) = map Vertices $ nonEmptyShrinks v shrink (ViewPort v) = map ViewPort $ shrink v shrink (VoroMargin v) = map VoroMargin $ shrink v shrink (Weight v) = map Weight $ shrink v shrink (Width v) = map Width $ shrink v shrink (XDotVersion v) = map XDotVersion $ shrink v shrink (XLabel v) = map XLabel $ shrink v shrink (XLP v) = map XLP $ shrink v shrink (UnknownAttribute a v) = liftM2 UnknownAttribute (liftM (filter validUnknown) shrink a) (shrink v) {- delete to here -} instance Arbitrary GraphvizCommand where arbitrary = arbBounded instance Arbitrary ArrowType where arbitrary = liftM AType -- Arrow specifications have between 1 and 4 elements. $ sized (\ s -> resize (min s 4) arbList) shrink (AType as) = map AType $ nonEmptyShrinks as instance Arbitrary ArrowShape where arbitrary = arbBounded instance Arbitrary ArrowModifier where arbitrary = liftM2 ArrMod arbitrary arbitrary instance Arbitrary ArrowFill where arbitrary = arbBounded instance Arbitrary ArrowSide where arbitrary = arbBounded instance Arbitrary LabelScheme where arbitrary = arbBounded instance Arbitrary Rect where arbitrary = liftM2 Rect point2D point2D shrink (Rect p1 p2) = do p1s <- shrink p1 p2s <- shrink p2 return $ Rect p1s p2s instance Arbitrary Point where -- Pretty sure points have to be positive... arbitrary = liftM4 Point posArbitrary posArbitrary posZ arbitrary where posZ = liftArbitrary posArbitrary shrink p = do x' <- shrink $ xCoord p y' <- shrink $ yCoord p z' <- shrinkM $ zCoord p return $ Point x' y' z' False point2D :: Gen Point point2D = liftM2 createPoint posArbitrary posArbitrary instance Arbitrary ClusterMode where arbitrary = arbBounded instance Arbitrary DirType where arbitrary = arbBounded instance Arbitrary DEConstraints where arbitrary = arbBounded instance Arbitrary DPoint where arbitrary = oneof [ liftM DVal arbitrary , liftM PVal point2D ] shrink (DVal d) = map DVal $ shrink d shrink (PVal p) = map PVal $ shrink p instance Arbitrary SVGFontNames where arbitrary = arbBounded instance Arbitrary GraphSize where arbitrary = liftM3 GSize arbitrary arbitrary arbitrary shrink gs = do w' <- shrink $ width gs h' <- shrinkM $ height gs return $ GSize w' h' False instance Arbitrary ModeType where arbitrary = arbBounded instance Arbitrary Model where arbitrary = arbBounded instance Arbitrary Label where arbitrary = oneof [ liftM StrLabel arbitrary , liftM HtmlLabel arbitrary , liftM RecordLabel $ suchThat arbList notStr ] shrink (StrLabel str) = map StrLabel $ shrink str shrink (HtmlLabel html) = map HtmlLabel $ shrink html shrink (RecordLabel fs) = map RecordLabel . filter notStr $ listShrink fs notStr :: RecordFields -> Bool notStr [FieldLabel{}] = False -- Just in case notStr _ = True arbField :: Bool -> Int -> Gen RecordField arbField b s = resize s' . oneof . bool id ((:) genFlipped) b $ [ liftM2 LabelledTarget arbitrary arbitrary , liftM PortName arbitrary , liftM FieldLabel arbitrary ] where genFlipped = liftM FlipFields $ listOf1 (sized $ arbField False) s' = min 3 s instance Arbitrary RecordField where arbitrary = sized (arbField True) shrink (LabelledTarget f l) = [PortName f, FieldLabel l] shrink (PortName f) = map PortName $ shrink f shrink (FieldLabel l) = map FieldLabel $ shrink l shrink (FlipFields fs) = map FlipFields $ listShrink fs instance Arbitrary Overlap where arbitrary = oneof [ simpleOverlap , liftM PrismOverlap arbitrary ] where -- Have to do this by hand since Overlap can't have Bounded and -- Enum instances simpleOverlap = elements [ KeepOverlaps , ScaleOverlaps , ScaleXYOverlaps , VoronoiOverlap , CompressOverlap , VpscOverlap , IpsepOverlap ] shrink (PrismOverlap mi) = map PrismOverlap $ shrink mi shrink _ = [] instance Arbitrary LayerSep where -- Since Arbitrary isn't stateful, we can't generate an arbitrary -- one because of arbLayerName arbitrary = return . LSep . T.pack $ layerSep initialState instance Arbitrary LayerListSep where -- Since Arbitrary isn't stateful, we can't generate an arbitrary -- one because of arbLayerName arbitrary = return . LLSep . T.pack $ layerListSep initialState instance Arbitrary LayerList where arbitrary = liftM LL $ listOf1 arbName where arbName = suchThat arbitrary isLayerName isLayerName LRName{} = True isLayerName _ = False shrink (LL ll) = map LL $ nonEmptyShrinks ll instance Arbitrary LayerRangeElem where arbitrary = oneof [ liftM LRID arbitrary , liftM2 LRS arbitrary arbitrary ] shrink (LRID nm) = map LRID $ shrink nm shrink (LRS l1 l2) = [LRID l1, LRID l2] instance Arbitrary LayerID where arbitrary = oneof [ return AllLayers , liftM LRInt arbitrary , liftM LRName $ suchThat arbLayerName lrnameCheck ] shrink AllLayers = [] shrink (LRInt i) = map LRInt $ shrink i shrink (LRName nm) = map LRName . filter lrnameCheck $ shrink nm lrnameCheck :: Text -> Bool lrnameCheck = (/=) "all" instance Arbitrary Order where arbitrary = arbBounded instance Arbitrary OutputMode where arbitrary = arbBounded instance Arbitrary Pack where arbitrary = oneof [ return DoPack , return DontPack , liftM PackMargin arbitrary ] shrink (PackMargin m) = map PackMargin $ shrink m shrink _ = [] instance Arbitrary PackMode where arbitrary = oneof [ return PackNode , return PackClust , return PackGraph , liftM3 PackArray arbitrary arbitrary arbitrary ] shrink (PackArray c u mi) = map (PackArray c u) $ shrink mi shrink _ = [] instance Arbitrary Pos where arbitrary = oneof [ liftM PointPos arbitrary -- A single spline with only one point overall -- is just a point... , liftM SplinePos $ suchThat arbList validSplineList ] shrink (PointPos p) = map PointPos $ shrink p shrink (SplinePos ss) = map SplinePos . filter validSplineList $ nonEmptyShrinks ss validSplineList :: [Spline] -> Bool validSplineList [Spline Nothing Nothing [_]] = False validSplineList _ = True instance Arbitrary Spline where arbitrary = liftM3 Spline arbitrary arbitrary -- list of points must have length of 1 mod 3 $ suchThat arbitrary ((==) 1 . flip mod 3 . length) shrink (Spline Nothing Nothing [p]) = map (Spline Nothing Nothing . return) $ shrink p -- We're not going to be shrinking the points in the list; just -- making sure that its length is === 1 mod 3 shrink (Spline ms me ps) = do mss <- shrinkM ms mes <- shrinkM me pss <- rem2 ps return $ Spline mss mes pss where rem1 [] = [] rem1 (a:as) = as : map (a:) (rem1 as) rem2 = nub . concatMap rem1 . rem1 instance Arbitrary EdgeType where arbitrary = arbBounded instance Arbitrary PageDir where arbitrary = arbBounded instance Arbitrary QuadType where arbitrary = arbBounded instance Arbitrary Root where arbitrary = oneof [ return IsCentral , return NotCentral , liftM NodeName arbitrary ] shrink (NodeName nm) = map NodeName $ shrink nm shrink _ = [] instance Arbitrary RankType where arbitrary = arbBounded instance Arbitrary RankDir where arbitrary = arbBounded instance Arbitrary Shape where arbitrary = arbBounded instance Arbitrary SmoothType where arbitrary = arbBounded instance Arbitrary StartType where arbitrary = oneof [ liftM StartStyle arbitrary , liftM StartSeed arbitrary , liftM2 StartStyleSeed arbitrary arbitrary ] shrink StartStyle{} = [] -- No shrinks for STStyle shrink (StartSeed ss) = map StartSeed $ shrink ss shrink (StartStyleSeed st ss) = map (StartStyleSeed st) $ shrink ss instance Arbitrary STStyle where arbitrary = arbBounded instance Arbitrary StyleItem where arbitrary = liftM2 SItem arbitrary (listOf arbStyleName) -- Can't use this because of what shrink on the individual strings -- might do. -- shrink (SItem sn opts) = map (SItem sn) $ shrink opts instance Arbitrary StyleName where arbitrary = oneof [ defaultStyles , liftM DD $ suchThat arbStyleName notDefault ] where defaultStyles = elements [ Dashed , Dotted , Bold , Invisible , Filled , Striped , Wedged , Diagonals , Rounded , Tapered , Radial ] notDefault = flip notElem [ "dashed" , "dotted" , "solid" , "bold" , "invis" , "filled" , "striped" , "wedged" , "diagonals" , "rounded" , "tapered" , "radial" ] instance Arbitrary PortPos where arbitrary = oneof [ liftM2 LabelledPort arbitrary arbitrary , liftM CompassPoint arbitrary ] shrink (LabelledPort pn mc) = map (flip LabelledPort mc) $ shrink pn shrink _ = [] instance Arbitrary CompassPoint where arbitrary = arbBounded instance Arbitrary ViewPort where arbitrary = liftM4 VP arbitrary arbitrary arbitrary arbitrary shrink (VP w h z f) = case sVPs of [_] -> [] _ -> sVPs where sVPs = do ws <- shrink w hs <- shrink h zs <- shrink z fs <- shrinkM f return $ VP ws hs zs fs instance Arbitrary FocusType where arbitrary = oneof [ liftM XY arbitrary , liftM NodeFocus $ suchThat arbitrary (T.all ((/=) ',')) ] shrink (XY p) = map XY $ shrink p shrink (NodeFocus str) = map NodeFocus $ shrink str instance Arbitrary VerticalPlacement where arbitrary = arbBounded instance Arbitrary Paths where arbitrary = liftM Paths $ listOf1 arbFilePath shrink (Paths ps) = map Paths $ nonEmptyShrinks' ps arbFilePath :: Gen FilePath arbFilePath = suchThat arbString (searchPathSeparator `notElem`) instance Arbitrary ScaleType where arbitrary = arbBounded instance Arbitrary Justification where arbitrary = arbBounded instance Arbitrary Ratios where arbitrary = oneof [ liftM AspectRatio posArbitrary , namedRats ] where namedRats = elements [ FillRatio , CompressRatio , ExpandRatio , AutoRatio ] shrink (AspectRatio r) = map (AspectRatio . fromPositive) . shrink $ Positive r shrink _ = [] instance Arbitrary ColorScheme where arbitrary = oneof [ return X11 , liftM Brewer arbitrary ] shrink (Brewer bs) = map Brewer $ shrink bs shrink _ = [] instance Arbitrary BrewerScheme where arbitrary = liftM2 BScheme arbitrary arbitrary -- Not /quite/ right, but close enough shrink (BScheme nm l) = map (BScheme nm) $ shrink l instance Arbitrary BrewerName where arbitrary = arbBounded instance Arbitrary Color where arbitrary = oneof [ liftM3 RGB arbitrary arbitrary arbitrary , liftM4 RGBA arbitrary arbitrary arbitrary arbitrary , liftM3 HSV zeroOne zeroOne zeroOne , liftM X11Color arbitrary , liftM SVGColor arbitrary , liftM BrewerColor arbitrary ] where zeroOne = choose (0,1) shrink (RGB r g b) = do rs <- shrink r gs <- shrink g bs <- shrink b return $ RGB rs gs bs shrink (RGBA r g b a) = RGB r g b : do rs <- shrink r gs <- shrink g bs <- shrink b as <- shrink a return $ RGBA rs gs bs as shrink (BrewerColor c) = map BrewerColor $ shrink c shrink _ = [] -- Shrinking 0<=h,s,v<=1 does nothing -- | No guarantees are made as to sanity of generated weightings. instance Arbitrary WeightedColor where arbitrary = liftM2 WC arbitrary arbitrary -- No color shrinks to itself, so no sanity checking needed. shrink (WC c mw) = do c' <- shrink c mw' <- shrink mw return $ WC c' mw' instance Arbitrary X11Color where arbitrary = arbBounded instance Arbitrary SVGColor where arbitrary = arbBounded -- | Not quite right as the values can get too high/low, but should -- suffice for printing/parsing purposes. instance Arbitrary BrewerColor where arbitrary = liftM2 BC arbitrary arbitrary shrink (BC s c) = map (BC s) $ shrink c instance Arbitrary Html.Label where arbitrary = sized $ arbHtml True shrink (Html.Text txts) = map Html.Text $ listShrink txts shrink (Html.Table tbl) = map Html.Table $ shrink tbl -- Note: for the most part, Html.Label values are very repetitive (and -- furthermore, they end up chewing a large amount of memory). As -- such, use resize to limit how large the actual Html.Label values -- become. arbHtml :: Bool -> Int -> Gen Html.Label arbHtml table s = resize' $ frequency options where s' = min 2 s resize' = if not table then resize s' else id allowTable = if table then (:) (1, arbTbl) else id arbTbl = liftM Html.Table arbitrary options = allowTable [ (20, liftM Html.Text . sized $ arbHtmlTexts table) ] arbHtmlTexts :: Bool -> Int -> Gen Html.Text arbHtmlTexts fnt s = liftM simplifyHtmlText . resize s' . listOf1 . sized $ arbHtmlText fnt where s' = min s 5 -- When parsing, all textual characters are parsed together; thus, -- make sure we generate them like that. simplifyHtmlText :: Html.Text -> Html.Text simplifyHtmlText = map head . groupBy sameType where sameType Html.Str{} Html.Str{} = True sameType Html.Newline{} Html.Newline{} = True sameType Html.Font{} Html.Font{} = True sameType (Html.Format fmt1 _) (Html.Format fmt2 _) = fmt1 == fmt2 sameType _ _ = False instance Arbitrary Html.TextItem where arbitrary = sized $ arbHtmlText True shrink (Html.Str str) = map Html.Str . filter (not . T.null) . map T.strip $ shrink str shrink (Html.Newline as) = map Html.Newline $ shrinkHtmlAttrs as shrink hf@(Html.Font as txt) = do as' <- shrinkHtmlAttrs as txt' <- shrinkL txt returnCheck hf $ Html.Font as' txt' shrink (Html.Format _ txt) = txt arbHtmlText :: Bool -> Int -> Gen Html.TextItem arbHtmlText font s = frequency options where allowFonts = if font then (++) recHtmlText else id s' = min 2 s arbRec = resize s' . sized $ arbHtmlTexts False recHtmlText = [ (1, liftM2 Html.Font arbHtmlAttrs arbRec) , (3, liftM2 Html.Format arbitrary arbRec) ] options = allowFonts [ (10, liftM Html.Str (suchThat (liftM T.strip arbitrary) (not . T.null))) , (10, liftM Html.Newline arbHtmlAttrs) ] instance Arbitrary Html.Format where arbitrary = arbBounded instance Arbitrary Html.Table where arbitrary = liftM3 Html.HTable (liftArbitrary arbHtmlAttrs) arbHtmlAttrs (sized arbRows) where arbRows s = resize (min s 10) arbList shrink (Html.HTable fas as rs) = liftM3 Html.HTable shrinkFont (shrinkHtmlAttrs as) (shrinkL rs) where shrinkFont = liftShrink shrinkHtmlAttrs fas #if !MIN_VERSION_QuickCheck(2,10,0) liftArbitrary :: Gen a -> Gen (Maybe a) liftArbitrary gen = frequency [(1, return Nothing), (3, liftM Just gen)] liftShrink :: (a -> [a]) -> Maybe a -> [Maybe a] liftShrink shr (Just x) = Nothing : map Just (shr x) liftShrink _ Nothing = [] #endif instance Arbitrary Html.Row where arbitrary = frequency [ (5, liftM Html.Cells arbList) , (1, return Html.HorizontalRule) ] shrink hr@(Html.Cells cs) = delete hr . map Html.Cells $ shrinkL cs shrink _ = [] instance Arbitrary Html.Cell where arbitrary = frequency [ (5, liftM2 Html.LabelCell arbitrary . sized $ arbHtml False) , (3, liftM2 Html.ImgCell arbitrary arbitrary) , (1, return Html.VerticalRule) ] shrink lc@(Html.LabelCell as h) = do as' <- shrink as h' <- shrink h returnCheck lc $ Html.LabelCell as' h' shrink (Html.ImgCell as ic) = map (Html.ImgCell as) $ shrink ic shrink _ = [] instance Arbitrary Html.Img where arbitrary = liftM Html.Img arbitrary arbHtmlAttrs :: Gen Html.Attributes arbHtmlAttrs = sized (\s -> resize (min 5 s) arbitrary) shrinkHtmlAttrs :: Html.Attributes -> [Html.Attributes] shrinkHtmlAttrs = listShrink instance Arbitrary Html.Attribute where arbitrary = oneof [ liftM Html.Align arbitrary , liftM Html.BAlign arbitrary , liftM Html.BGColor arbitrary , liftM Html.Border arbitrary , liftM Html.CellBorder arbitrary , liftM Html.CellPadding arbitrary , liftM Html.CellSpacing arbitrary , liftM Html.Color arbitrary , liftM Html.ColSpan arbitrary , liftM Html.Columns arbitrary , liftM Html.Face arbitrary , liftM Html.FixedSize arbitrary , liftM Html.GradientAngle arbitrary , liftM Html.Height arbitrary , liftM Html.HRef arbitrary , liftM Html.ID arbitrary , liftM Html.PointSize arbitrary , liftM Html.Port arbitrary , liftM Html.Rows arbitrary , liftM Html.RowSpan arbitrary , liftM Html.Scale arbitrary , liftM Html.Sides (fmap nub (sized (\s -> resize (min s 4) arbitrary))) -- Will never have more than 4 values , liftM Html.Src arbString , liftM Html.Style arbitrary , liftM Html.Target arbitrary , liftM Html.Title arbitrary , liftM Html.VAlign arbitrary , liftM Html.Width arbitrary ] shrink (Html.Align v) = map Html.Align $ shrink v shrink (Html.BAlign v) = map Html.BAlign $ shrink v shrink (Html.BGColor v) = map Html.BGColor $ shrink v shrink (Html.Border v) = map Html.Border $ shrink v shrink (Html.CellBorder v) = map Html.CellBorder $ shrink v shrink (Html.CellPadding v) = map Html.CellPadding $ shrink v shrink (Html.CellSpacing v) = map Html.CellSpacing $ shrink v shrink (Html.Color v) = map Html.Color $ shrink v shrink (Html.ColSpan v) = map Html.ColSpan $ shrink v shrink (Html.Columns v) = map Html.Columns $ shrink v shrink (Html.Face v) = map Html.Face $ shrink v shrink (Html.FixedSize v) = map Html.FixedSize $ shrink v shrink (Html.GradientAngle v) = map Html.GradientAngle $ shrink v shrink (Html.Height v) = map Html.Height $ shrink v shrink (Html.HRef v) = map Html.HRef $ shrink v shrink (Html.ID v) = map Html.ID $ shrink v shrink (Html.PointSize v) = map Html.PointSize $ shrink v shrink (Html.Port v) = map Html.Port $ shrink v shrink (Html.Rows v) = map Html.Rows $ shrink v shrink (Html.RowSpan v) = map Html.RowSpan $ shrink v shrink (Html.Scale v) = map Html.Scale $ shrink v shrink (Html.Sides v) = map Html.Sides $ listShrink' v shrink (Html.Src v) = map Html.Src $ shrinkString v shrink (Html.Style v) = map Html.Style $ shrink v shrink (Html.Target v) = map Html.Target $ shrink v shrink (Html.Title v) = map Html.Title $ shrink v shrink (Html.VAlign v) = map Html.VAlign $ shrink v shrink (Html.Width v) = map Html.Width $ shrink v instance Arbitrary Html.Scale where arbitrary = arbBounded instance Arbitrary Html.Align where arbitrary = arbBounded instance Arbitrary Html.VAlign where arbitrary = arbBounded instance Arbitrary Html.CellFormat where arbitrary = arbBounded instance Arbitrary Html.Side where arbitrary = arbBounded instance Arbitrary Html.Style where arbitrary = arbBounded instance Arbitrary PortName where arbitrary = liftM PN $ suchThat arbitrary (liftM2 (&&) (T.all (/=':')) notCP) shrink = map PN . filter notCP . shrink . portName notCP :: Text -> Bool notCP = flip Map.notMember compassLookup instance Arbitrary Number where arbitrary = frequency [ (3, liftM Dbl $ suchThat arbitrary notInt) , (1, liftM Int arbitrary) ] shrink (Int i) = map Int $ shrink i shrink (Dbl d) = map Dbl $ filter notInt $ shrink d instance Arbitrary Normalized where arbitrary = oneof [ elements [IsNormalized, NotNormalized] , liftM NormalizedAngle arbitrary ] shrink (NormalizedAngle a) = map NormalizedAngle $ shrink a shrink _ = [] #if !MIN_VERSION_QuickCheck(2,9,0) instance Arbitrary Version where arbitrary = liftM (createVersion . map getPositive) arbList shrink = map createVersion . nonEmptyShrinks . versionBranch #endif instance Arbitrary NodeSize where arbitrary = arbBounded {- As of Graphviz 2.36.0 this was commented out; as such it might come back, so leave this here in case we need it again. instance Arbitrary AspectType where arbitrary = oneof [ liftM RatioOnly arbitrary , liftM2 RatioPassCount arbitrary posArbitrary ] shrink (RatioOnly d) = map RatioOnly $ shrink d shrink (RatioPassCount d i) = do ds <- shrink d is <- shrink i return $ RatioPassCount ds is -} graphviz-2999.20.2.0/tests/Data/GraphViz/Testing/Instances/Common.hs0000644000000000000000000000437114535166704023143 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Testing.Instances.Common() Description : Attribute instances for Arbitrary. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Testing.Instances.Common ( gaGraph , gaSubGraph , gaClusters ) where import Data.GraphViz.Testing.Instances.Attributes import Data.GraphViz.Testing.Instances.Helpers import Data.GraphViz.Algorithms (CanonicaliseOptions (..)) import Data.GraphViz.Attributes (Attributes) import Data.GraphViz.Types.Internal.Common (DotEdge (..), DotNode (..), GlobalAttributes (..), GraphID (..)) import Test.QuickCheck import Control.Monad (liftM, liftM2, liftM3) -- ----------------------------------------------------------------------------- -- Common values instance Arbitrary GraphID where arbitrary = oneof [ liftM Str arbitrary , liftM Num arbitrary ] shrink (Str s) = map Str $ shrink s shrink (Num n) = map Num $ shrink n instance (Arbitrary n) => Arbitrary (DotNode n) where arbitrary = liftM2 DotNode arbitrary arbNodeAttrs shrink (DotNode n as) = map (DotNode n) $ shrink as instance (Arbitrary n) => Arbitrary (DotEdge n) where arbitrary = liftM3 DotEdge arbitrary arbitrary arbEdgeAttrs shrink (DotEdge f t as) = map (DotEdge f t) $ shrink as instance Arbitrary GlobalAttributes where arbitrary = gaGraph shrink (GraphAttrs atts) = map GraphAttrs $ nonEmptyShrinks atts shrink (NodeAttrs atts) = map NodeAttrs $ nonEmptyShrinks atts shrink (EdgeAttrs atts) = map EdgeAttrs $ nonEmptyShrinks atts gaGraph :: Gen GlobalAttributes gaGraph = gaFor arbGraphAttrs gaSubGraph :: Gen GlobalAttributes gaSubGraph = gaFor arbSubGraphAttrs gaClusters :: Gen GlobalAttributes gaClusters = gaFor arbClusterAttrs gaFor :: Gen Attributes -> Gen GlobalAttributes gaFor g = oneof [ liftM GraphAttrs g , liftM NodeAttrs arbNodeAttrs , liftM EdgeAttrs arbEdgeAttrs ] instance Arbitrary CanonicaliseOptions where arbitrary = liftM2 COpts arbitrary arbitrary graphviz-2999.20.2.0/tests/Data/GraphViz/Testing/Instances/Canonical.hs0000644000000000000000000000417414535166704023603 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Testing.Instances.Canonical Description : Canonical dot graph instances for Arbitrary. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Testing.Instances.Canonical where import Data.GraphViz.Testing.Instances.Common import Data.GraphViz.Testing.Instances.Helpers import Data.GraphViz.Internal.Util (bool) import Data.GraphViz.Types.Canonical import Test.QuickCheck import Control.Monad (liftM2, liftM4) -- ----------------------------------------------------------------------------- -- Defining Arbitrary instances for the overall types instance (Eq n, Arbitrary n) => Arbitrary (DotGraph n) where arbitrary = liftM4 DotGraph arbitrary arbitrary arbitrary arbitrary shrink (DotGraph str dir gid stmts) = map (DotGraph str dir gid) $ shrink stmts instance (Eq n, Arbitrary n) => Arbitrary (DotStatements n) where arbitrary = sized (arbDS gaGraph True) shrink ds@(DotStmts gas sgs ns es) = do gas' <- shrink gas sgs' <- shrink sgs ns' <- shrink ns es' <- shrink es returnCheck ds $ DotStmts gas' sgs' ns' es' -- | If 'True', generate 'DotSubGraph's; otherwise don't. arbDS :: (Arbitrary n, Eq n) => Gen GlobalAttributes -> Bool -> Int -> Gen (DotStatements n) arbDS ga haveSGs s = liftM4 DotStmts (listOf ga) genSGs arbitrary arbitrary where s' = min s 2 genSGs = if haveSGs then resize s' arbitrary else return [] instance (Eq n, Arbitrary n) => Arbitrary (DotSubGraph n) where arbitrary = do isClust <- arbitrary let ga = bool gaSubGraph gaClusters isClust liftM2 (DotSG isClust) arbitrary (sized $ arbDS ga False) shrink (DotSG isCl mid stmts) = map (DotSG isCl mid) $ shrink stmts graphviz-2999.20.2.0/tests/Data/GraphViz/Testing/Instances/Generalised.hs0000644000000000000000000000526414535166704024137 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_HADDOCK hide #-} {- | Module : Data.GraphViz.Testing.Instances.Generalised Description : Generalised dot graph instances for Arbitrary. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Testing.Instances.Generalised where import Data.GraphViz.Testing.Instances.Attributes () import Data.GraphViz.Testing.Instances.Common import Data.GraphViz.Testing.Instances.Helpers () import Data.GraphViz.Internal.Util (bool) import Data.GraphViz.Types.Generalised import Test.QuickCheck import Control.Monad (liftM, liftM2, liftM4) import qualified Data.Sequence as Seq -- ----------------------------------------------------------------------------- -- Defining Arbitrary instances for the generalised types instance (Arbitrary n) => Arbitrary (DotGraph n) where arbitrary = liftM4 DotGraph arbitrary arbitrary arbitrary genDStmts shrink (DotGraph str dir gid stmts) = map (DotGraph str dir gid) $ shrinkDStmts stmts genDStmts :: (Arbitrary n) => Gen (DotStatements n) genDStmts = sized (arbDS gaGraph True) genDStmt :: (Arbitrary n) => Gen GlobalAttributes -> Bool -> Gen (DotStatement n) genDStmt ga haveSGs = frequency . bool id ((1,genSG):) haveSGs $ [ (3, liftM GA ga) , (5, liftM DN arbitrary) , (7, liftM DE arbitrary) ] where genSG = liftM SG arbitrary shrinkDStmts :: (Arbitrary n) => DotStatements n -> [DotStatements n] shrinkDStmts gds | len == 1 = map Seq.singleton . shrink $ Seq.index gds 0 | otherwise = [gds1, gds2] where len = Seq.length gds -- Halve the sequence (gds1, gds2) = (len `div` 2) `Seq.splitAt` gds instance (Arbitrary n) => Arbitrary (DotStatement n) where arbitrary = genDStmt gaGraph True shrink (GA ga) = map GA $ shrink ga shrink (SG sg) = map SG $ shrink sg shrink (DN dn) = map DN $ shrink dn shrink (DE de) = map DE $ shrink de -- | If 'True', generate 'GDotSubGraph's; otherwise don't. arbDS :: (Arbitrary n) => Gen GlobalAttributes -> Bool -> Int -> Gen (DotStatements n) arbDS ga haveSGs s = liftM Seq.fromList . resize s' . listOf $ genDStmt ga haveSGs where s' = min s 10 instance (Arbitrary n) => Arbitrary (DotSubGraph n) where arbitrary = do isClust <- arbitrary let ga = bool gaSubGraph gaClusters isClust liftM2 (DotSG isClust) arbitrary (sized $ arbDS ga False) shrink (DotSG isCl mid stmts) = map (DotSG isCl mid) $ shrinkDStmts stmts graphviz-2999.20.2.0/tests/Data/GraphViz/Testing/Instances/Graph.hs0000644000000000000000000000172714535166704022756 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_HADDOCK hide #-} {-# LANGUAGE FlexibleInstances #-} {- | Module : Data.GraphViz.Testing.Instances.Graph Description : Graph dot graph instances for Arbitrary. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Testing.Instances.Graph where import Data.GraphViz.Testing.Instances.Canonical() import Data.GraphViz.Types.Graph import Data.GraphViz.Types(fromCanonical) import Test.QuickCheck import Control.Monad(liftM) -- ----------------------------------------------------------------------------- -- | Can't directly create one of these as it might not match the -- internal format directly; as such, have to use the inefficient -- 'fromCanonical' route. instance (Arbitrary n, Ord n) => Arbitrary (DotGraph n) where arbitrary = liftM fromCanonical arbitrary shrink = map fromCanonical . shrink . toCanonical graphviz-2999.20.2.0/tests/Data/GraphViz/Testing/Proxy.hs0000644000000000000000000000104014535166704021073 0ustar0000000000000000{-# LANGUAGE KindSignatures #-} {- | Module : Data.GraphViz.Testing.Proxy Description : Proxy implementation Copyright : Matthew Sackman, Ivan Lazar Miljenovic License : BSD3 Maintainer : Ivan.Miljenovic@gmail.com Data.Proxy was added to base with GHC 7.8.1, and we want to test for older versions than that. -} module Data.GraphViz.Testing.Proxy where -------------------------------------------------------------------------------- data DGProxy (dg :: * -> *) = DGProxy deriving (Eq, Ord, Show, Read) graphviz-2999.20.2.0/tests/Data/GraphVizSpec.hs0000644000000000000000000000174514535166704017164 0ustar0000000000000000{- | Module : Data.GraphVizSpec Description : Testing algorithms Copyright : Matthew Sackman, Ivan Lazar Miljenovic License : BSD3 Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphVizSpec (spec) where import Data.GraphViz.Testing.Instances () import Data.GraphViz.Testing.Properties (prop_dotizeAugment, prop_dotizeAugmentUniq, prop_dotizeHasAugment) import Test.Hspec (Spec) import Test.Hspec.QuickCheck (prop) import Data.Graph.Inductive.PatriciaTree (Gr) -------------------------------------------------------------------------------- spec :: Spec spec = do prop "FGL Graphs are augmentable" (prop_dotizeAugment :: GrType -> Bool) prop "Ensure augmentation is valid" (prop_dotizeHasAugment :: GrType -> Bool) prop "Unique edges in augmented FGL Graphs" (prop_dotizeAugmentUniq :: GrType -> Bool) type GrType = Gr Char Double graphviz-2999.20.2.0/tests/Data/GraphViz/AlgorithmsSpec.hs0000644000000000000000000000275014535166704021272 0ustar0000000000000000{- | Module : Data.GraphViz.AlgorithmsSpec Description : Testing algorithms Copyright : Matthew Sackman, Ivan Lazar Miljenovic License : BSD3 Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.AlgorithmsSpec (spec) where import Data.GraphViz.Algorithms (CanonicaliseOptions) import Data.GraphViz.Testing.Instances () import Data.GraphViz.Testing.Properties (prop_canonicalise, prop_canonicaliseEdges, prop_canonicaliseNodes, prop_transitive, prop_transitiveNodes) import Data.GraphViz.Types.Canonical (DotGraph) import Test.Hspec (Spec) import Test.Hspec.QuickCheck (prop) -------------------------------------------------------------------------------- spec :: Spec spec = do prop "Canonicalisation should be idempotent" (prop_canonicalise :: CanonicaliseOptions -> DotGraph Int -> Bool) prop "Canonicalisation shouldn't change any nodes" (prop_canonicaliseNodes :: CanonicaliseOptions -> DotGraph Int -> Bool) prop "Canonicalisation shouldn't change any edges" (prop_canonicaliseEdges :: CanonicaliseOptions -> DotGraph Int -> Bool) prop "Transitive reduction should be idempotent" (prop_transitive :: CanonicaliseOptions -> DotGraph Int -> Bool) prop "Transitive reduction shouldn't change any nodes" (prop_transitiveNodes :: CanonicaliseOptions -> DotGraph Int -> Bool) graphviz-2999.20.2.0/tests/Data/GraphViz/Attributes/CompleteSpec.hs0000644000000000000000000000135114535166704023053 0ustar0000000000000000{- | Module : Data.GraphViz.Attributes.CompleteSpec Description : Attribute testing Copyright : Ivan Lazar Miljenovic License : BSD3 Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Attributes.CompleteSpec (spec) where import Data.GraphViz.Attributes.Complete (Attributes) import Data.GraphViz.Testing.Instances () import Data.GraphViz.Testing.Properties (prop_printParseListID) import Test.Hspec (Spec) import Test.Hspec.QuickCheck (prop) import Test.QuickCheck (Property) -------------------------------------------------------------------------------- spec :: Spec spec = prop "Printing and parsing of attributes" (prop_printParseListID :: Attributes -> Property) graphviz-2999.20.2.0/tests/Data/GraphViz/Attributes/HTMLSpec.hs0000644000000000000000000000145314535166704022052 0ustar0000000000000000{- | Module : Data.GraphViz.Attributes.HTMLSpec Description : HTML label testing Copyright : Ivan Lazar Miljenovic License : BSD3 Maintainer : Ivan.Miljenovic@gmail.com This is in addition to "Data.GraphViz.Attributes.CompleteSpec" as HTML labels are also likely to have their own quirks for testing. -} module Data.GraphViz.Attributes.HTMLSpec (spec) where import Data.GraphViz.Attributes.HTML (Label) import Data.GraphViz.Testing.Instances () import Data.GraphViz.Testing.Properties (prop_printParseID) import Test.Hspec (Spec) import Test.Hspec.QuickCheck (prop) -------------------------------------------------------------------------------- spec :: Spec spec = prop "Printing and parsing of HTML labels" (prop_printParseID :: Label -> Bool) graphviz-2999.20.2.0/tests/Data/GraphViz/PreProcessingSpec.hs0000644000000000000000000000127614535166704021746 0ustar0000000000000000{- | Module : Data.GraphViz.PreProcessingSpec Description : Test pre-processing Copyright : Matthew Sackman, Ivan Lazar Miljenovic License : BSD3 Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.PreProcessingSpec where import Data.GraphViz.Testing.Instances () import Data.GraphViz.Testing.Properties (prop_preProcessingID) import Data.GraphViz.Types.Canonical (DotGraph) import Test.Hspec (Spec) import Test.Hspec.QuickCheck (prop) -------------------------------------------------------------------------------- spec :: Spec spec = prop "Preprocessing doesn't change Dot code" (prop_preProcessingID :: DotGraph Int -> Bool) graphviz-2999.20.2.0/tests/Data/GraphViz/Types/CanonicalSpec.hs0000644000000000000000000000311014535166704022143 0ustar0000000000000000{- | Module : Data.GraphViz.Types.CanonicalSpec Description : Testing canonical graph representation Copyright : Matthew Sackman, Ivan Lazar Miljenovic License : BSD3 Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Types.CanonicalSpec (spec) where import Data.GraphViz.Testing.Instances () import Data.GraphViz.Testing.Properties (prop_findAllEdges, prop_findAllNodes, prop_findAllNodesE, prop_generalisedSameDot, prop_noGraphInfo, prop_printParseID) import Data.GraphViz.Testing.Proxy (DGProxy(..)) import Data.GraphViz.Types.Canonical (DotGraph) import Test.Hspec (Spec) import Test.Hspec.QuickCheck (prop) import Data.Graph.Inductive.PatriciaTree (Gr) -------------------------------------------------------------------------------- spec :: Spec spec = do prop "Generalising a graph doesn't change Dot code" (prop_generalisedSameDot :: DotGraph Int -> Bool) prop "Printing and parsing Dot graph" (prop_printParseID :: DotGraph Int -> Bool) prop "Find all nodes in a Dot graph" (prop_findAllNodes dproxy :: Gr () () -> Bool) prop "Find all nodes in an node-less Dot graph" (prop_findAllNodesE dproxy :: Gr () () -> Bool) prop "Find all edges in a Dot graph" (prop_findAllEdges dproxy :: Gr () () -> Bool) prop "Plain Dot graphs should have no structural information" (prop_noGraphInfo dproxy :: Gr () () -> Bool) dproxy :: DGProxy DotGraph dproxy = DGProxy graphviz-2999.20.2.0/tests/Data/GraphViz/Types/GeneralisedSpec.hs0000644000000000000000000000263514535166704022511 0ustar0000000000000000{- | Module : Data.GraphViz.Types.GeneralisedSpec Description : Testing generalised graph representation Copyright : Matthew Sackman, Ivan Lazar Miljenovic License : BSD3 Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Types.GeneralisedSpec (spec) where import Data.GraphViz.Testing.Instances () import Data.GraphViz.Testing.Properties (prop_findAllEdges, prop_findAllNodes, prop_findAllNodesE, prop_noGraphInfo, prop_printParseID) import Data.GraphViz.Testing.Proxy (DGProxy(..)) import Data.GraphViz.Types.Generalised (DotGraph) import Test.Hspec (Spec) import Test.Hspec.QuickCheck (prop) import Data.Graph.Inductive.PatriciaTree (Gr) -------------------------------------------------------------------------------- spec :: Spec spec = do prop "Printing and parsing Dot graph" (prop_printParseID :: DotGraph Int -> Bool) prop "Find all nodes in a Dot graph" (prop_findAllNodes dproxy :: Gr () () -> Bool) prop "Find all nodes in an node-less Dot graph" (prop_findAllNodesE dproxy :: Gr () () -> Bool) prop "Find all edges in a Dot graph" (prop_findAllEdges dproxy :: Gr () () -> Bool) prop "Plain Dot graphs should have no structural information" (prop_noGraphInfo dproxy :: Gr () () -> Bool) dproxy :: DGProxy DotGraph dproxy = DGProxy graphviz-2999.20.2.0/tests/Data/GraphViz/Types/GraphSpec.hs0000644000000000000000000000445314535166704021330 0ustar0000000000000000{- | Module : Data.GraphViz.Types.GraphSpec Description : Testing graph-based graph representation Copyright : Matthew Sackman, Ivan Lazar Miljenovic License : BSD3 Maintainer : Ivan.Miljenovic@gmail.com -} module Data.GraphViz.Types.GraphSpec (spec) where import Data.GraphViz.Testing.Instances () import Data.GraphViz.Testing.Properties (prop_findAllEdges, prop_findAllNodes, prop_findAllNodesE, prop_noGraphInfo, prop_printParseID) import Data.GraphViz.Testing.Proxy (DGProxy(..)) import Data.GraphViz.Types (edgeInformation) import Data.GraphViz.Types.Graph (Context(..), DotEdge(..), DotGraph, DotNode(..), addEdge, emptyGraph, mkGraph, (&)) import Test.Hspec (Spec, describe, it) import Test.Hspec.QuickCheck (prop) import Data.Graph.Inductive.PatriciaTree (Gr) -------------------------------------------------------------------------------- spec :: Spec spec = do prop "Printing and parsing Dot graph" (prop_printParseID :: DotGraph Int -> Bool) prop "Find all nodes in a Dot graph" (prop_findAllNodes dproxy :: Gr () () -> Bool) prop "Find all nodes in an node-less Dot graph" (prop_findAllNodesE dproxy :: Gr () () -> Bool) prop "Find all edges in a Dot graph" (prop_findAllEdges dproxy :: Gr () () -> Bool) prop "Plain Dot graphs should have no structural information" (prop_noGraphInfo dproxy :: Gr () () -> Bool) describe "issue#28" $ do it "mkGraph retains proper edge order" $ hasEdge (mkGraph [DotNode 0 [], DotNode 1 []] [DotEdge 0 1 []]) (0,1) it "& retains proper edge order" $ hasEdge (Cntxt { node = 1, inCluster = Nothing, attributes = [], predecessors = [(0,[])], successors = []} & Cntxt { node = 0, inCluster = Nothing, attributes = [], predecessors = [], successors = []} & emptyGraph) (0,1) it "addEdge retains proper edge order" $ hasEdge (addEdge 0 1 [] (mkGraph [DotNode 0 [], DotNode 1 []] [])) (0,1) dproxy :: DGProxy DotGraph dproxy = DGProxy hasEdge :: DotGraph Int -> (Int,Int) -> Bool hasEdge dg (f,t) = edgeInformation False dg == [DotEdge f t []] graphviz-2999.20.2.0/tests/Spec.hs0000644000000000000000000000010514535166704014625 0ustar0000000000000000{-# OPTIONS_GHC -F -pgmF hspec-discover -optF --module-name=Spec #-} graphviz-2999.20.2.0/utils/Benchmark.hs0000644000000000000000000201143714535166704015637 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {- | Module : Benchmark Description : Benchmarking utilities for graphviz Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com -} module Main where import Data.GraphViz hiding (DotGraph) import Data.GraphViz.Types.Generalised import Criterion.Main import Control.DeepSeq import Data.Text.Lazy (Text) -- ----------------------------------------------------------------------------- main :: IO () main = defaultMain [ bench "Parsing in-memory GDotGraph" $ nf parseGDG largeDefined , bench "Printing GDotGraph" $ nf printDotGraph largeGraph ] parseGDG :: Text -> DotGraph Int parseGDG = parseDotGraph instance (Show a) => NFData (DotGraph a) where rnf = rnf . show largeGraph :: DotGraph Int largeGraph = parseGDG largeDefined largeDefined :: Text largeDefined = "digraph \"Entire Codebase\" {\n\tnode [label=\"\\N\", margin=\"0.4,0.1\", style=filled];\n\tsubgraph cluster_Class_Arbitrary {\n\t\tgraph [label=\"Class: Arbitrary\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=rosybrown1];\n\t\tsubgraph cluster_Class_Arbitrary_Data_DotEdgea {\n\t\t\tgraph [label=\"Instance for: (DotEdge a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1530 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1614 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_DotGrapha {\n\t\t\tgraph [label=\"Instance for: (DotGraph a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1531 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1615 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_DotNodea {\n\t\t\tgraph [label=\"Instance for: (DotNode a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1532 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1616 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_DotStatementsa {\n\t\t\tgraph [label=\"Instance for: (DotStatements a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1533 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1617 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_DotSubGrapha {\n\t\t\tgraph [label=\"Instance for: (DotSubGraph a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1534 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1618 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_GDotGrapha {\n\t\t\tgraph [label=\"Instance for: (GDotGraph a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1535 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1619 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_GDotStatementa {\n\t\t\tgraph [label=\"Instance for: (GDotStatement a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1536 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1620 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_GDotSubGrapha {\n\t\t\tgraph [label=\"Instance for: (GDotSubGraph a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1537 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1621 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_gne {\n\t\t\tgraph [label=\"Instance for: (g n e)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1665 [label=\"Data.GraphViz.Testing.Instances.FGL\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1666 [label=\"Data.GraphViz.Testing.Instances.FGL\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=cyan];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_ArrowFill {\n\t\t\tgraph [label=\"Instance for: ArrowFill\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1538 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_ArrowModifier {\n\t\t\tgraph [label=\"Instance for: ArrowModifier\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1539 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_ArrowShape {\n\t\t\tgraph [label=\"Instance for: ArrowShape\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1540 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_ArrowSide {\n\t\t\tgraph [label=\"Instance for: ArrowSide\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1541 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_ArrowType {\n\t\t\tgraph [label=\"Instance for: ArrowType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1542 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1622 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_AspectType {\n\t\t\tgraph [label=\"Instance for: AspectType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1543 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1623 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Attribute {\n\t\t\tgraph [label=\"Instance for: Attribute\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1544 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1624 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_BrewerName {\n\t\t\tgraph [label=\"Instance for: BrewerName\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1545 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_ClusterMode {\n\t\t\tgraph [label=\"Instance for: ClusterMode\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1546 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Color {\n\t\t\tgraph [label=\"Instance for: Color\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1547 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1625 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_ColorScheme {\n\t\t\tgraph [label=\"Instance for: ColorScheme\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1548 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1626 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_CompassPoint {\n\t\t\tgraph [label=\"Instance for: CompassPoint\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1549 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_DEConstraints {\n\t\t\tgraph [label=\"Instance for: DEConstraints\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1550 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_DPoint {\n\t\t\tgraph [label=\"Instance for: DPoint\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1551 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1627 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_DirType {\n\t\t\tgraph [label=\"Instance for: DirType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1552 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_EdgeType {\n\t\t\tgraph [label=\"Instance for: EdgeType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1553 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_FocusType {\n\t\t\tgraph [label=\"Instance for: FocusType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1554 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1628 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_GlobalAttributes {\n\t\t\tgraph [label=\"Instance for: GlobalAttributes\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1555 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1629 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_GraphID {\n\t\t\tgraph [label=\"Instance for: GraphID\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1556 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1630 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_HtmlAlign {\n\t\t\tgraph [label=\"Instance for: HtmlAlign\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1557 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_HtmlAttribute {\n\t\t\tgraph [label=\"Instance for: HtmlAttribute\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1558 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1631 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_HtmlCell {\n\t\t\tgraph [label=\"Instance for: HtmlCell\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1559 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1632 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_HtmlImg {\n\t\t\tgraph [label=\"Instance for: HtmlImg\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1560 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_HtmlLabel {\n\t\t\tgraph [label=\"Instance for: HtmlLabel\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1561 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1633 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_HtmlRow {\n\t\t\tgraph [label=\"Instance for: HtmlRow\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1562 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1634 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_HtmlScale {\n\t\t\tgraph [label=\"Instance for: HtmlScale\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1563 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_HtmlTable {\n\t\t\tgraph [label=\"Instance for: HtmlTable\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1564 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1635 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_HtmlTextItem {\n\t\t\tgraph [label=\"Instance for: HtmlTextItem\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1565 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1636 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_HtmlVAlign {\n\t\t\tgraph [label=\"Instance for: HtmlVAlign\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1566 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Justification {\n\t\t\tgraph [label=\"Instance for: Justification\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1567 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Label {\n\t\t\tgraph [label=\"Instance for: Label\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1568 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1637 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_LayerID {\n\t\t\tgraph [label=\"Instance for: LayerID\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1569 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1638 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_LayerList {\n\t\t\tgraph [label=\"Instance for: LayerList\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1570 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1639 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_LayerRange {\n\t\t\tgraph [label=\"Instance for: LayerRange\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1571 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1640 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_ModeType {\n\t\t\tgraph [label=\"Instance for: ModeType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1572 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Model {\n\t\t\tgraph [label=\"Instance for: Model\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1573 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_OutputMode {\n\t\t\tgraph [label=\"Instance for: OutputMode\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1574 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Overlap {\n\t\t\tgraph [label=\"Instance for: Overlap\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1575 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1641 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Pack {\n\t\t\tgraph [label=\"Instance for: Pack\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1576 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1642 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_PackMode {\n\t\t\tgraph [label=\"Instance for: PackMode\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1577 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1643 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_PageDir {\n\t\t\tgraph [label=\"Instance for: PageDir\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1578 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Point {\n\t\t\tgraph [label=\"Instance for: Point\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1579 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1644 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_PortName {\n\t\t\tgraph [label=\"Instance for: PortName\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1580 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1645 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_PortPos {\n\t\t\tgraph [label=\"Instance for: PortPos\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1581 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1646 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Pos {\n\t\t\tgraph [label=\"Instance for: Pos\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1582 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1647 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_QuadType {\n\t\t\tgraph [label=\"Instance for: QuadType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1583 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_RankDir {\n\t\t\tgraph [label=\"Instance for: RankDir\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1584 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_RankType {\n\t\t\tgraph [label=\"Instance for: RankType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1585 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Ratios {\n\t\t\tgraph [label=\"Instance for: Ratios\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1586 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1648 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_RecordField {\n\t\t\tgraph [label=\"Instance for: RecordField\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1587 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1649 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Rect {\n\t\t\tgraph [label=\"Instance for: Rect\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1588 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1650 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Root {\n\t\t\tgraph [label=\"Instance for: Root\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1589 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1651 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_STStyle {\n\t\t\tgraph [label=\"Instance for: STStyle\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1590 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_ScaleType {\n\t\t\tgraph [label=\"Instance for: ScaleType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1591 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Shape {\n\t\t\tgraph [label=\"Instance for: Shape\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1592 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_SmoothType {\n\t\t\tgraph [label=\"Instance for: SmoothType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1593 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_Spline {\n\t\t\tgraph [label=\"Instance for: Spline\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1594 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1652 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_StartType {\n\t\t\tgraph [label=\"Instance for: StartType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1595 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1653 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_StyleItem {\n\t\t\tgraph [label=\"Instance for: StyleItem\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1596 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_StyleName {\n\t\t\tgraph [label=\"Instance for: StyleName\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1597 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_VerticalPlacement {\n\t\t\tgraph [label=\"Instance for: VerticalPlacement\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1598 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_ViewPort {\n\t\t\tgraph [label=\"Instance for: ViewPort\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1599 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1654 [label=\"Data.GraphViz.Testing.Instances\\nshrink\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Arbitrary_Data_X11Color {\n\t\t\tgraph [label=\"Instance for: X11Color\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1600 [label=\"Data.GraphViz.Testing.Instances\\narbitrary\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\t1889 [label=\"Unknown Module\\narbitrary\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1900 [label=\"Unknown Module\\nshrink\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1530 -> 1889 [penwidth=\"2.386294361119891\", color=black];\n\t\t1531 -> 1889 [penwidth=\"2.386294361119891\", color=black];\n\t\t1532 -> 1889 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1534 -> 1889 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1535 -> 1889 [penwidth=\"2.09861228866811\", color=black];\n\t\t1536 -> 1889 [penwidth=\"2.386294361119891\", color=black];\n\t\t1537 -> 1889 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1539 -> 1889 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1543 -> 1889 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1544 -> 1889 [penwidth=\"5.68213122712422\", color=black];\n\t\t1547 -> 1889 [penwidth=\"3.1972245773362196\", color=black];\n\t\t1548 -> 1889 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1551 -> 1889 [penwidth=1, color=black];\n\t\t1554 -> 1889 [penwidth=1, color=black];\n\t\t1556 -> 1889 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1558 -> 1889 [penwidth=\"3.833213344056216\", color=black];\n\t\t1559 -> 1889 [penwidth=\"2.09861228866811\", color=black];\n\t\t1560 -> 1889 [penwidth=1, color=black];\n\t\t1564 -> 1889 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1568 -> 1889 [penwidth=1, color=black];\n\t\t1569 -> 1889 [penwidth=1, color=black];\n\t\t1570 -> 1889 [penwidth=1, color=black];\n\t\t1571 -> 1889 [penwidth=\"2.09861228866811\", color=black];\n\t\t1575 -> 1889 [penwidth=1, color=black];\n\t\t1576 -> 1889 [penwidth=1, color=black];\n\t\t1577 -> 1889 [penwidth=\"2.09861228866811\", color=black];\n\t\t1579 -> 1889 [penwidth=1, color=black];\n\t\t1581 -> 1889 [penwidth=\"2.09861228866811\", color=black];\n\t\t1582 -> 1889 [penwidth=1, color=black];\n\t\t1594 -> 1889 [penwidth=\"2.09861228866811\", color=black];\n\t\t1595 -> 1889 [penwidth=\"2.386294361119891\", color=black];\n\t\t1596 -> 1889 [penwidth=1, color=black];\n\t\t1599 -> 1889 [penwidth=\"2.386294361119891\", color=black];\n\t\t1615 -> 1900 [penwidth=1, color=black];\n\t\t1618 -> 1900 [penwidth=1, color=black];\n\t\t1620 -> 1900 [penwidth=\"2.386294361119891\", color=black];\n\t\t1623 -> 1900 [penwidth=\"2.09861228866811\", color=black];\n\t\t1624 -> 1900 [penwidth=\"5.68213122712422\", color=black];\n\t\t1625 -> 1900 [penwidth=\"3.0794415416798357\", color=black];\n\t\t1626 -> 1900 [penwidth=1, color=black];\n\t\t1627 -> 1900 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1628 -> 1900 [penwidth=1, color=black];\n\t\t1630 -> 1900 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1631 -> 1900 [penwidth=\"4.091042453358316\", color=black];\n\t\t1632 -> 1900 [penwidth=\"2.09861228866811\", color=black];\n\t\t1633 -> 1900 [penwidth=1, color=black];\n\t\t1636 -> 1900 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1637 -> 1900 [penwidth=1, color=black];\n\t\t1638 -> 1900 [penwidth=1, color=black];\n\t\t1640 -> 1900 [penwidth=1, color=black];\n\t\t1641 -> 1900 [penwidth=1, color=black];\n\t\t1642 -> 1900 [penwidth=1, color=black];\n\t\t1643 -> 1900 [penwidth=1, color=black];\n\t\t1644 -> 1900 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1646 -> 1900 [penwidth=1, color=black];\n\t\t1647 -> 1900 [penwidth=1, color=black];\n\t\t1648 -> 1900 [penwidth=1, color=black];\n\t\t1649 -> 1900 [penwidth=1, color=black];\n\t\t1650 -> 1900 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1652 -> 1900 [penwidth=1, color=black];\n\t\t1653 -> 1900 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1654 -> 1900 [penwidth=\"2.09861228866811\", color=black];\n\t\t1665 -> 1889 [penwidth=\"2.09861228866811\", color=black];\n\t\t1889 -> 1530 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1531 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1532 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1533 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1534 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1535 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1536 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1537 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1538 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1539 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1540 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1541 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1542 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1543 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1544 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1545 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1546 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1547 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1548 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1549 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1550 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1551 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1552 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1553 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1554 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1555 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1556 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1557 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1558 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1559 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1560 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1561 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1562 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1563 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1564 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1565 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1566 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1567 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1568 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1569 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1570 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1571 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1572 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1573 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1574 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1575 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1576 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1577 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1578 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1579 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1580 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1581 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1582 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1583 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1584 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1585 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1586 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1587 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1588 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1589 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1590 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1591 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1592 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1593 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1594 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1595 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1596 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1597 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1598 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1599 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1600 [penwidth=1, color=navy, dir=none];\n\t\t1889 -> 1665 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1614 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1615 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1616 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1617 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1618 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1619 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1620 [penwidth=\"2.386294361119891\", color=navy, dir=none];\n\t\t1900 -> 1621 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1622 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1623 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1624 [penwidth=\"5.976733742420574\", color=navy, dir=none];\n\t\t1900 -> 1625 [penwidth=\"2.386294361119891\", color=navy, dir=none];\n\t\t1900 -> 1626 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1627 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1628 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1629 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1900 -> 1630 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1900 -> 1631 [penwidth=\"4.091042453358316\", color=navy, dir=none];\n\t\t1900 -> 1632 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1633 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1634 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1635 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1636 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1900 -> 1637 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1900 -> 1638 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1900 -> 1639 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1640 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1641 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1642 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1643 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1644 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1645 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1646 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1647 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1648 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1649 [penwidth=\"2.386294361119891\", color=navy, dir=none];\n\t\t1900 -> 1650 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1651 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1652 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1900 -> 1653 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1900 -> 1654 [penwidth=1, color=navy, dir=none];\n\t\t1900 -> 1666 [penwidth=1, color=navy, dir=none];\n\t}\n\tsubgraph cluster_Class_DotRepr {\n\t\tgraph [label=\"Class: DotRepr\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=rosybrown1];\n\t\tsubgraph cluster_Class_DotRepr_Data_GDotGraphn {\n\t\t\tgraph [label=\"Instance for: GDotGraph n\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1779 [label=\"Data.GraphViz.Types.Generalised\\nedgeInformation\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1793 [label=\"Data.GraphViz.Types.Generalised\\ngetID\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1794 [label=\"Data.GraphViz.Types.Generalised\\ngraphIsDirected\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1795 [label=\"Data.GraphViz.Types.Generalised\\ngraphIsStrict\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1796 [label=\"Data.GraphViz.Types.Generalised\\ngraphStructureInformation\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1799 [label=\"Data.GraphViz.Types.Generalised\\nmakeStrict\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1800 [label=\"Data.GraphViz.Types.Generalised\\nnodeInformation\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1814 [label=\"Data.GraphViz.Types.Generalised\\nsetID\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\t1891 [label=\"Unknown Module\\nedgeInformation\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1893 [label=\"Unknown Module\\ngetID\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1894 [label=\"Unknown Module\\ngraphIsDirected\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1895 [label=\"Unknown Module\\ngraphIsStrict\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1896 [label=\"Unknown Module\\ngraphStructureInformation\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1897 [label=\"Unknown Module\\nmakeStrict\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1898 [label=\"Unknown Module\\nnodeInformation\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1899 [label=\"Unknown Module\\nsetID\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1891 -> 1779 [penwidth=1, color=navy, dir=none];\n\t\t1893 -> 1793 [penwidth=1, color=navy, dir=none];\n\t\t1894 -> 1794 [penwidth=1, color=navy, dir=none];\n\t\t1895 -> 1795 [penwidth=1, color=navy, dir=none];\n\t\t1896 -> 1796 [penwidth=1, color=navy, dir=none];\n\t\t1897 -> 1799 [penwidth=1, color=navy, dir=none];\n\t\t1898 -> 1800 [penwidth=1, color=navy, dir=none];\n\t\t1899 -> 1814 [penwidth=1, color=navy, dir=none];\n\t}\n\tsubgraph cluster_Class_Eq {\n\t\tgraph [label=\"Class: Eq\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=rosybrown1];\n\t\tsubgraph cluster_Class_Eq_Data_SameAttr {\n\t\t\tgraph [label=\"Instance for: SameAttr\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1827 [label=\"Data.GraphViz.Types.State\\n==\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\t1888 [label=\"Unknown Module\\n==\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1888 -> 1827 [penwidth=1, color=navy, dir=none];\n\t}\n\tsubgraph cluster_Class_Functor {\n\t\tgraph [label=\"Class: Functor\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=rosybrown1];\n\t\tsubgraph cluster_Class_Functor_Data_DotEdge {\n\t\t\tgraph [label=\"Instance for: DotEdge\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1703 [label=\"Data.GraphViz.Types.Common\\nfmap\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Functor_Data_DotNode {\n\t\t\tgraph [label=\"Instance for: DotNode\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1704 [label=\"Data.GraphViz.Types.Common\\nfmap\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Functor_Data_GDotGraph {\n\t\t\tgraph [label=\"Instance for: GDotGraph\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1780 [label=\"Data.GraphViz.Types.Generalised\\nfmap\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Functor_Data_GDotStatement {\n\t\t\tgraph [label=\"Instance for: GDotStatement\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1781 [label=\"Data.GraphViz.Types.Generalised\\nfmap\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Functor_Data_GDotSubGraph {\n\t\t\tgraph [label=\"Instance for: GDotSubGraph\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1782 [label=\"Data.GraphViz.Types.Generalised\\nfmap\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\t1892 [label=\"Unknown Module\\nfmap\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1780 -> 1892 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1781 -> 1892 [penwidth=\"2.09861228866811\", color=black];\n\t\t1782 -> 1892 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1892 -> 1703 [penwidth=1, color=navy, dir=none];\n\t\t1892 -> 1704 [penwidth=1, color=navy, dir=none];\n\t\t1892 -> 1780 [penwidth=1, color=navy, dir=none];\n\t\t1892 -> 1781 [penwidth=\"2.386294361119891\", color=navy, dir=none];\n\t\t1892 -> 1782 [penwidth=1, color=navy, dir=none];\n\t}\n\tsubgraph cluster_Class_Labellable {\n\t\tgraph [label=\"Class: Labellable\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=rosybrown1];\n\t\tsubgraph cluster_Class_Labellable_Data_PortNameEscString {\n\t\t\tgraph [label=\"Instance for: (PortName, EscString)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t538 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Labellable_Data_Bool {\n\t\t\tgraph [label=\"Instance for: Bool\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t539 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Labellable_Data_Char {\n\t\t\tgraph [label=\"Instance for: Char\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t540 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Labellable_Data_Double {\n\t\t\tgraph [label=\"Instance for: Double\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t541 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Labellable_Data_EscString {\n\t\t\tgraph [label=\"Instance for: EscString\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t542 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Labellable_Data_HtmlLabel {\n\t\t\tgraph [label=\"Instance for: HtmlLabel\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t543 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Labellable_Data_HtmlTable {\n\t\t\tgraph [label=\"Instance for: HtmlTable\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t544 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Labellable_Data_HtmlText {\n\t\t\tgraph [label=\"Instance for: HtmlText\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t545 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Labellable_Data_Int {\n\t\t\tgraph [label=\"Instance for: Int\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t546 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Labellable_Data_PortName {\n\t\t\tgraph [label=\"Instance for: PortName\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t547 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Labellable_Data_RecordField {\n\t\t\tgraph [label=\"Instance for: RecordField\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t548 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_Labellable_Data_RecordFields {\n\t\t\tgraph [label=\"Instance for: RecordFields\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t549 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\t537 [label=\"Data.GraphViz.Attributes\\ntoLabel\", style=\"filled,solid\", shape=doubleoctagon, fillcolor=goldenrod];\n\t\t537 -> 538 [penwidth=1, color=navy, dir=none];\n\t\t537 -> 539 [penwidth=1, color=navy, dir=none];\n\t\t537 -> 540 [penwidth=1, color=navy, dir=none];\n\t\t537 -> 541 [penwidth=1, color=navy, dir=none];\n\t\t537 -> 542 [penwidth=1, color=navy, dir=none];\n\t\t537 -> 543 [penwidth=1, color=navy, dir=none];\n\t\t537 -> 544 [penwidth=1, color=navy, dir=none];\n\t\t537 -> 545 [penwidth=1, color=navy, dir=none];\n\t\t537 -> 546 [penwidth=1, color=navy, dir=none];\n\t\t537 -> 547 [penwidth=1, color=navy, dir=none];\n\t\t537 -> 548 [penwidth=1, color=navy, dir=none];\n\t\t537 -> 549 [penwidth=1, color=navy, dir=none];\n\t\t538 -> 537 [penwidth=1, color=black];\n\t\t539 -> 537 [penwidth=1, color=black];\n\t\t540 -> 537 [penwidth=1, color=black];\n\t\t541 -> 537 [penwidth=1, color=black];\n\t\t544 -> 537 [penwidth=1, color=black];\n\t\t545 -> 537 [penwidth=1, color=black];\n\t\t546 -> 537 [penwidth=1, color=black];\n\t\t547 -> 537 [penwidth=1, color=black];\n\t\t548 -> 537 [penwidth=1, color=black];\n\t}\n\tsubgraph cluster_Class_Ord {\n\t\tgraph [label=\"Class: Ord\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=rosybrown1];\n\t\tsubgraph cluster_Class_Ord_Data_SameAttr {\n\t\t\tgraph [label=\"Instance for: SameAttr\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1842 [label=\"Data.GraphViz.Types.State\\ncompare\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\t1890 [label=\"Unknown Module\\ncompare\", style=\"filled,dotted\", shape=doubleoctagon, fillcolor=khaki];\n\t\t1842 -> 1890 [penwidth=1, color=black];\n\t\t1890 -> 1842 [penwidth=1, color=navy, dir=none];\n\t}\n\tsubgraph cluster_Class_ParseDot {\n\t\tgraph [label=\"Class: ParseDot\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=rosybrown1];\n\t\tsubgraph cluster_Class_ParseDot_Data_DotEdgea {\n\t\t\tgraph [label=\"Instance for: (DotEdge a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1715 [label=\"Data.GraphViz.Types.Common\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1729 [label=\"Data.GraphViz.Types.Common\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1737 [label=\"Data.GraphViz.Types.Common\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1741 [label=\"Data.GraphViz.Types.Common\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_DotNodea {\n\t\t\tgraph [label=\"Instance for: (DotNode a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1716 [label=\"Data.GraphViz.Types.Common\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1730 [label=\"Data.GraphViz.Types.Common\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1738 [label=\"Data.GraphViz.Types.Common\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1742 [label=\"Data.GraphViz.Types.Common\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_GDotGrapha {\n\t\t\tgraph [label=\"Instance for: (GDotGraph a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1801 [label=\"Data.GraphViz.Types.Generalised\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1807 [label=\"Data.GraphViz.Types.Generalised\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_GDotStatementa {\n\t\t\tgraph [label=\"Instance for: (GDotStatement a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1802 [label=\"Data.GraphViz.Types.Generalised\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1805 [label=\"Data.GraphViz.Types.Generalised\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1808 [label=\"Data.GraphViz.Types.Generalised\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1810 [label=\"Data.GraphViz.Types.Generalised\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_GDotSubGrapha {\n\t\t\tgraph [label=\"Instance for: (GDotSubGraph a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1803 [label=\"Data.GraphViz.Types.Generalised\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1806 [label=\"Data.GraphViz.Types.Generalised\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1809 [label=\"Data.GraphViz.Types.Generalised\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1811 [label=\"Data.GraphViz.Types.Generalised\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_ArrowFill {\n\t\t\tgraph [label=\"Instance for: ArrowFill\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t437 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t467 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_ArrowModifier {\n\t\t\tgraph [label=\"Instance for: ArrowModifier\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t468 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_ArrowShape {\n\t\t\tgraph [label=\"Instance for: ArrowShape\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t469 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_ArrowSide {\n\t\t\tgraph [label=\"Instance for: ArrowSide\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t438 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t470 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_ArrowType {\n\t\t\tgraph [label=\"Instance for: ArrowType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t471 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_AspectType {\n\t\t\tgraph [label=\"Instance for: AspectType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t439 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t472 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Attribute {\n\t\t\tgraph [label=\"Instance for: Attribute\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t440 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t461 [label=\"Data.GraphViz.Attributes\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t473 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Bool {\n\t\t\tgraph [label=\"Instance for: Bool\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1417 [label=\"Data.GraphViz.Parsing\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_BrewerName {\n\t\t\tgraph [label=\"Instance for: BrewerName\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1210 [label=\"Data.GraphViz.Attributes.Colors\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Char {\n\t\t\tgraph [label=\"Instance for: Char\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1389 [label=\"Data.GraphViz.Parsing\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1411 [label=\"Data.GraphViz.Parsing\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1418 [label=\"Data.GraphViz.Parsing\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1426 [label=\"Data.GraphViz.Parsing\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_ClusterMode {\n\t\t\tgraph [label=\"Instance for: ClusterMode\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t474 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Color {\n\t\t\tgraph [label=\"Instance for: Color\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1208 [label=\"Data.GraphViz.Attributes.Colors\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1209 [label=\"Data.GraphViz.Attributes.Colors\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1211 [label=\"Data.GraphViz.Attributes.Colors\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1214 [label=\"Data.GraphViz.Attributes.Colors\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_ColorScheme {\n\t\t\tgraph [label=\"Instance for: ColorScheme\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1212 [label=\"Data.GraphViz.Attributes.Colors\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_CompassPoint {\n\t\t\tgraph [label=\"Instance for: CompassPoint\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1360 [label=\"Data.GraphViz.Attributes.Internal\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_DEConstraints {\n\t\t\tgraph [label=\"Instance for: DEConstraints\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t475 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_DPoint {\n\t\t\tgraph [label=\"Instance for: DPoint\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t441 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t476 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_DirType {\n\t\t\tgraph [label=\"Instance for: DirType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t477 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Double {\n\t\t\tgraph [label=\"Instance for: Double\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1412 [label=\"Data.GraphViz.Parsing\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1419 [label=\"Data.GraphViz.Parsing\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1427 [label=\"Data.GraphViz.Parsing\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_EdgeType {\n\t\t\tgraph [label=\"Instance for: EdgeType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t442 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t478 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_FocusType {\n\t\t\tgraph [label=\"Instance for: FocusType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t443 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t479 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_GlobalAttributes {\n\t\t\tgraph [label=\"Instance for: GlobalAttributes\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1717 [label=\"Data.GraphViz.Types.Common\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1731 [label=\"Data.GraphViz.Types.Common\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1739 [label=\"Data.GraphViz.Types.Common\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1743 [label=\"Data.GraphViz.Types.Common\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_GraphID {\n\t\t\tgraph [label=\"Instance for: GraphID\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1718 [label=\"Data.GraphViz.Types.Common\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1740 [label=\"Data.GraphViz.Types.Common\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_HtmlAlign {\n\t\t\tgraph [label=\"Instance for: HtmlAlign\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1281 [label=\"Data.GraphViz.Attributes.HTML\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1301 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_HtmlAttribute {\n\t\t\tgraph [label=\"Instance for: HtmlAttribute\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1282 [label=\"Data.GraphViz.Attributes.HTML\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1297 [label=\"Data.GraphViz.Attributes.HTML\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1302 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1311 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_HtmlCell {\n\t\t\tgraph [label=\"Instance for: HtmlCell\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1283 [label=\"Data.GraphViz.Attributes.HTML\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1298 [label=\"Data.GraphViz.Attributes.HTML\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1303 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1312 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_HtmlImg {\n\t\t\tgraph [label=\"Instance for: HtmlImg\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1284 [label=\"Data.GraphViz.Attributes.HTML\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1304 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_HtmlLabel {\n\t\t\tgraph [label=\"Instance for: HtmlLabel\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1285 [label=\"Data.GraphViz.Attributes.HTML\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1305 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_HtmlRow {\n\t\t\tgraph [label=\"Instance for: HtmlRow\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1286 [label=\"Data.GraphViz.Attributes.HTML\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1299 [label=\"Data.GraphViz.Attributes.HTML\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1306 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1313 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_HtmlScale {\n\t\t\tgraph [label=\"Instance for: HtmlScale\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1287 [label=\"Data.GraphViz.Attributes.HTML\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1307 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_HtmlTable {\n\t\t\tgraph [label=\"Instance for: HtmlTable\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1288 [label=\"Data.GraphViz.Attributes.HTML\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1308 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_HtmlTextItem {\n\t\t\tgraph [label=\"Instance for: HtmlTextItem\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1289 [label=\"Data.GraphViz.Attributes.HTML\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1300 [label=\"Data.GraphViz.Attributes.HTML\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1309 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1314 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_HtmlVAlign {\n\t\t\tgraph [label=\"Instance for: HtmlVAlign\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1290 [label=\"Data.GraphViz.Attributes.HTML\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1310 [label=\"Data.GraphViz.Attributes.HTML\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Int {\n\t\t\tgraph [label=\"Instance for: Int\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1420 [label=\"Data.GraphViz.Parsing\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Justification {\n\t\t\tgraph [label=\"Instance for: Justification\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t480 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Label {\n\t\t\tgraph [label=\"Instance for: Label\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t444 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t481 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_LayerID {\n\t\t\tgraph [label=\"Instance for: LayerID\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t445 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t482 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_LayerList {\n\t\t\tgraph [label=\"Instance for: LayerList\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t446 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t483 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_LayerRange {\n\t\t\tgraph [label=\"Instance for: LayerRange\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t447 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t484 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_ModeType {\n\t\t\tgraph [label=\"Instance for: ModeType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t485 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Model {\n\t\t\tgraph [label=\"Instance for: Model\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t486 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_OutputMode {\n\t\t\tgraph [label=\"Instance for: OutputMode\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t487 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Overlap {\n\t\t\tgraph [label=\"Instance for: Overlap\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t488 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Pack {\n\t\t\tgraph [label=\"Instance for: Pack\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t489 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_PackMode {\n\t\t\tgraph [label=\"Instance for: PackMode\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t490 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_PageDir {\n\t\t\tgraph [label=\"Instance for: PageDir\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t491 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Point {\n\t\t\tgraph [label=\"Instance for: Point\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t448 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t492 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t511 [label=\"Data.GraphViz.Attributes\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_PortName {\n\t\t\tgraph [label=\"Instance for: PortName\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1357 [label=\"Data.GraphViz.Attributes.Internal\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1361 [label=\"Data.GraphViz.Attributes.Internal\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_PortPos {\n\t\t\tgraph [label=\"Instance for: PortPos\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1358 [label=\"Data.GraphViz.Attributes.Internal\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1362 [label=\"Data.GraphViz.Attributes.Internal\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Pos {\n\t\t\tgraph [label=\"Instance for: Pos\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t449 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t493 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_QuadType {\n\t\t\tgraph [label=\"Instance for: QuadType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t494 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_RankDir {\n\t\t\tgraph [label=\"Instance for: RankDir\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t495 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_RankType {\n\t\t\tgraph [label=\"Instance for: RankType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t496 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Ratios {\n\t\t\tgraph [label=\"Instance for: Ratios\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t497 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_RecordField {\n\t\t\tgraph [label=\"Instance for: RecordField\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t450 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t462 [label=\"Data.GraphViz.Attributes\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t498 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t512 [label=\"Data.GraphViz.Attributes\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Rect {\n\t\t\tgraph [label=\"Instance for: Rect\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t451 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t499 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Root {\n\t\t\tgraph [label=\"Instance for: Root\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t452 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t500 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_STStyle {\n\t\t\tgraph [label=\"Instance for: STStyle\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t501 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_ScaleType {\n\t\t\tgraph [label=\"Instance for: ScaleType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t502 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Shape {\n\t\t\tgraph [label=\"Instance for: Shape\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t503 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_SmoothType {\n\t\t\tgraph [label=\"Instance for: SmoothType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t504 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Spline {\n\t\t\tgraph [label=\"Instance for: Spline\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t453 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t505 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t513 [label=\"Data.GraphViz.Attributes\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_StartType {\n\t\t\tgraph [label=\"Instance for: StartType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t506 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_StyleItem {\n\t\t\tgraph [label=\"Instance for: StyleItem\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t454 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t463 [label=\"Data.GraphViz.Attributes\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t507 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t514 [label=\"Data.GraphViz.Attributes\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_StyleName {\n\t\t\tgraph [label=\"Instance for: StyleName\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t455 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t508 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_VerticalPlacement {\n\t\t\tgraph [label=\"Instance for: VerticalPlacement\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t509 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_ViewPort {\n\t\t\tgraph [label=\"Instance for: ViewPort\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t456 [label=\"Data.GraphViz.Attributes\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t510 [label=\"Data.GraphViz.Attributes\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Word16 {\n\t\t\tgraph [label=\"Instance for: Word16\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1421 [label=\"Data.GraphViz.Parsing\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_Word8 {\n\t\t\tgraph [label=\"Instance for: Word8\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1422 [label=\"Data.GraphViz.Parsing\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_X11Color {\n\t\t\tgraph [label=\"Instance for: X11Color\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1213 [label=\"Data.GraphViz.Attributes.Colors\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_ParseDot_Data_a {\n\t\t\tgraph [label=\"Instance for: [a]\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1390 [label=\"Data.GraphViz.Parsing\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1423 [label=\"Data.GraphViz.Parsing\\nparseUnqt\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_DefaultInstance_ParseDot {\n\t\t\tgraph [label=\"Default Instance\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1388 [label=\"Data.GraphViz.Parsing\\nparse\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1410 [label=\"Data.GraphViz.Parsing\\nparseList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1425 [label=\"Data.GraphViz.Parsing\\nparseUnqtList\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\t1387 [label=\"Data.GraphViz.Parsing\\nparse\", style=\"filled,solid\", shape=doubleoctagon, fillcolor=goldenrod];\n\t\t1409 [label=\"Data.GraphViz.Parsing\\nparseList\", style=\"filled,solid\", shape=doubleoctagon, fillcolor=goldenrod];\n\t\t1416 [label=\"Data.GraphViz.Parsing\\nparseUnqt\", style=\"filled,solid\", shape=doubleoctagon, fillcolor=goldenrod];\n\t\t1424 [label=\"Data.GraphViz.Parsing\\nparseUnqtList\", style=\"filled,solid\", shape=doubleoctagon, fillcolor=goldenrod];\n\t\t437 -> 1416 [penwidth=1, color=black];\n\t\t438 -> 1416 [penwidth=1, color=black];\n\t\t439 -> 1387 [penwidth=1, color=black];\n\t\t440 -> 1416 [penwidth=1, color=black];\n\t\t441 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t\t442 -> 1416 [penwidth=1, color=black];\n\t\t443 -> 1387 [penwidth=\"1.6931471805599454\", color=black];\n\t\t444 -> 1387 [penwidth=\"2.09861228866811\", color=black];\n\t\t445 -> 1387 [penwidth=1, color=black];\n\t\t446 -> 1416 [penwidth=1, color=black];\n\t\t447 -> 1387 [penwidth=1, color=black];\n\t\t447 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t\t448 -> 1416 [penwidth=1, color=black];\n\t\t449 -> 1416 [penwidth=1, color=black];\n\t\t450 -> 1416 [penwidth=1, color=black];\n\t\t451 -> 1416 [penwidth=1, color=black];\n\t\t452 -> 1387 [penwidth=1, color=black];\n\t\t453 -> 1416 [penwidth=1, color=black];\n\t\t454 -> 1387 [penwidth=1, color=black];\n\t\t454 -> 1416 [penwidth=1, color=black];\n\t\t455 -> 1416 [penwidth=1, color=black];\n\t\t456 -> 1416 [penwidth=1, color=black];\n\t\t461 -> 1424 [penwidth=1, color=black];\n\t\t462 -> 1424 [penwidth=1, color=black];\n\t\t463 -> 1387 [penwidth=1, color=black];\n\t\t463 -> 1424 [penwidth=1, color=black];\n\t\t468 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t\t471 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t\t472 -> 1416 [penwidth=1, color=black];\n\t\t473 -> 1387 [penwidth=1, color=black];\n\t\t475 -> 1387 [penwidth=1, color=black];\n\t\t476 -> 1416 [penwidth=1, color=black];\n\t\t478 -> 1387 [penwidth=1, color=black];\n\t\t479 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t\t481 -> 1416 [penwidth=\"2.09861228866811\", color=black];\n\t\t483 -> 1416 [penwidth=1, color=black];\n\t\t484 -> 1416 [penwidth=\"2.09861228866811\", color=black];\n\t\t488 -> 1387 [penwidth=1, color=black];\n\t\t489 -> 1416 [penwidth=1, color=black];\n\t\t490 -> 1416 [penwidth=1, color=black];\n\t\t492 -> 1416 [penwidth=1, color=black];\n\t\t493 -> 1416 [penwidth=1, color=black];\n\t\t494 -> 1387 [penwidth=1, color=black];\n\t\t497 -> 1416 [penwidth=1, color=black];\n\t\t498 -> 1416 [penwidth=1, color=black];\n\t\t500 -> 1416 [penwidth=1, color=black];\n\t\t505 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t\t506 -> 1416 [penwidth=\"2.386294361119891\", color=black];\n\t\t507 -> 1416 [penwidth=1, color=black];\n\t\t510 -> 1416 [penwidth=\"2.386294361119891\", color=black];\n\t\t511 -> 1416 [penwidth=1, color=black];\n\t\t512 -> 1416 [penwidth=1, color=black];\n\t\t513 -> 1416 [penwidth=1, color=black];\n\t\t514 -> 1416 [penwidth=1, color=black];\n\t\t1208 -> 1416 [penwidth=\"2.09861228866811\", color=black];\n\t\t1209 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1209 -> 1424 [penwidth=1, color=black];\n\t\t1211 -> 1387 [penwidth=\"2.09861228866811\", color=black];\n\t\t1211 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1212 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1214 -> 1416 [penwidth=1, color=black];\n\t\t1281 -> 1416 [penwidth=1, color=black];\n\t\t1282 -> 1416 [penwidth=1, color=black];\n\t\t1283 -> 1416 [penwidth=1, color=black];\n\t\t1284 -> 1416 [penwidth=1, color=black];\n\t\t1285 -> 1416 [penwidth=1, color=black];\n\t\t1286 -> 1416 [penwidth=1, color=black];\n\t\t1287 -> 1416 [penwidth=1, color=black];\n\t\t1288 -> 1416 [penwidth=1, color=black];\n\t\t1289 -> 1416 [penwidth=1, color=black];\n\t\t1290 -> 1416 [penwidth=1, color=black];\n\t\t1297 -> 1424 [penwidth=1, color=black];\n\t\t1298 -> 1424 [penwidth=1, color=black];\n\t\t1299 -> 1424 [penwidth=1, color=black];\n\t\t1300 -> 1424 [penwidth=1, color=black];\n\t\t1303 -> 1387 [penwidth=1, color=black];\n\t\t1303 -> 1416 [penwidth=1, color=black];\n\t\t1305 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1306 -> 1416 [penwidth=1, color=black];\n\t\t1308 -> 1416 [penwidth=1, color=black];\n\t\t1309 -> 1416 [penwidth=1, color=black];\n\t\t1311 -> 1416 [penwidth=1, color=black];\n\t\t1312 -> 1416 [penwidth=1, color=black];\n\t\t1313 -> 1416 [penwidth=1, color=black];\n\t\t1314 -> 1416 [penwidth=1, color=black];\n\t\t1357 -> 1416 [penwidth=1, color=black];\n\t\t1358 -> 1416 [penwidth=1, color=black];\n\t\t1362 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1387 -> 437 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 438 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 439 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 440 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 441 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 442 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 443 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 444 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 445 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 446 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 447 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 448 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 449 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 450 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 451 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 452 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 453 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 454 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 455 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 456 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1208 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1281 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1282 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1283 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1284 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1285 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1286 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1287 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1288 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1289 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1290 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1357 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1358 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1388 [penwidth=1, color=turquoise, dir=none];\n\t\t1387 -> 1389 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1390 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1715 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1716 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1717 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1718 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1801 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1802 [penwidth=1, color=navy, dir=none];\n\t\t1387 -> 1803 [penwidth=1, color=navy, dir=none];\n\t\t1388 -> 1416 [penwidth=1, color=black];\n\t\t1389 -> 1416 [penwidth=1, color=black];\n\t\t1390 -> 1409 [penwidth=1, color=chartreuse];\n\t\t1409 -> 461 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 462 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 463 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1209 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1297 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1298 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1299 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1300 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1410 [penwidth=1, color=turquoise, dir=none];\n\t\t1409 -> 1411 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1412 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1729 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1730 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1731 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1805 [penwidth=1, color=navy, dir=none];\n\t\t1409 -> 1806 [penwidth=1, color=navy, dir=none];\n\t\t1410 -> 1424 [penwidth=1, color=black];\n\t\t1412 -> 1387 [penwidth=1, color=black];\n\t\t1412 -> 1424 [penwidth=1, color=black];\n\t\t1416 -> 467 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 468 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 469 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 470 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 471 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 472 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 473 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 474 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 475 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 476 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 477 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 478 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 479 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 480 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 481 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 482 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 483 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 484 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 485 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 486 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 487 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 488 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 489 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 490 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 491 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 492 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 493 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 494 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 495 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 496 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 497 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 498 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 499 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 500 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 501 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 502 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 503 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 504 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 505 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 506 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 507 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 508 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 509 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 510 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1210 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1211 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1212 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1213 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1301 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1302 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1303 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1304 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1305 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1306 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1307 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1308 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1309 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1310 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1360 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1361 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1362 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1417 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1418 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1419 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1420 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1421 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1422 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1423 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1737 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1738 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1739 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1740 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1807 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1808 [penwidth=1, color=navy, dir=none];\n\t\t1416 -> 1809 [penwidth=1, color=navy, dir=none];\n\t\t1423 -> 1424 [penwidth=1, color=black];\n\t\t1424 -> 511 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 512 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 513 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 514 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1214 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1311 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1312 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1313 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1314 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1425 [penwidth=1, color=turquoise, dir=none];\n\t\t1424 -> 1426 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1427 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1741 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1742 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1743 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1810 [penwidth=1, color=navy, dir=none];\n\t\t1424 -> 1811 [penwidth=1, color=navy, dir=none];\n\t\t1425 -> 1416 [penwidth=1, color=black];\n\t\t1427 -> 1416 [penwidth=1, color=black];\n\t\t1715 -> 1416 [penwidth=1, color=black];\n\t\t1716 -> 1416 [penwidth=1, color=black];\n\t\t1717 -> 1416 [penwidth=1, color=black];\n\t\t1718 -> 1387 [penwidth=1, color=black];\n\t\t1729 -> 1424 [penwidth=1, color=black];\n\t\t1730 -> 1424 [penwidth=1, color=black];\n\t\t1731 -> 1424 [penwidth=1, color=black];\n\t\t1739 -> 1387 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1740 -> 1416 [penwidth=1, color=black];\n\t\t1743 -> 1387 [penwidth=1, color=black];\n\t\t1801 -> 1416 [penwidth=1, color=black];\n\t\t1802 -> 1416 [penwidth=1, color=black];\n\t\t1803 -> 1416 [penwidth=1, color=black];\n\t\t1805 -> 1424 [penwidth=1, color=black];\n\t\t1806 -> 1424 [penwidth=1, color=black];\n\t\t1808 -> 1416 [penwidth=\"2.386294361119891\", color=black];\n\t\t1810 -> 1387 [penwidth=1, color=black];\n\t\t1811 -> 1416 [penwidth=1, color=black];\n\t}\n\tsubgraph cluster_Class_PrintDot {\n\t\tgraph [label=\"Class: PrintDot\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=rosybrown1];\n\t\tsubgraph cluster_Class_PrintDot_Data_DotEdgea {\n\t\t\tgraph [label=\"Instance for: (DotEdge a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1708 [label=\"Data.GraphViz.Types.Common\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1766 [label=\"Data.GraphViz.Types.Common\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1770 [label=\"Data.GraphViz.Types.Common\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_DotNodea {\n\t\t\tgraph [label=\"Instance for: (DotNode a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1709 [label=\"Data.GraphViz.Types.Common\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1767 [label=\"Data.GraphViz.Types.Common\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1771 [label=\"Data.GraphViz.Types.Common\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_GDotGrapha {\n\t\t\tgraph [label=\"Instance for: (GDotGraph a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1821 [label=\"Data.GraphViz.Types.Generalised\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_GDotStatementa {\n\t\t\tgraph [label=\"Instance for: (GDotStatement a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1797 [label=\"Data.GraphViz.Types.Generalised\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1822 [label=\"Data.GraphViz.Types.Generalised\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1824 [label=\"Data.GraphViz.Types.Generalised\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_GDotSubGrapha {\n\t\t\tgraph [label=\"Instance for: (GDotSubGraph a)\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1798 [label=\"Data.GraphViz.Types.Generalised\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1823 [label=\"Data.GraphViz.Types.Generalised\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1825 [label=\"Data.GraphViz.Types.Generalised\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_ArrowFill {\n\t\t\tgraph [label=\"Instance for: ArrowFill\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t550 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_ArrowModifier {\n\t\t\tgraph [label=\"Instance for: ArrowModifier\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t551 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_ArrowShape {\n\t\t\tgraph [label=\"Instance for: ArrowShape\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t552 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_ArrowSide {\n\t\t\tgraph [label=\"Instance for: ArrowSide\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t553 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_ArrowType {\n\t\t\tgraph [label=\"Instance for: ArrowType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t554 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_AspectType {\n\t\t\tgraph [label=\"Instance for: AspectType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t520 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t555 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Attribute {\n\t\t\tgraph [label=\"Instance for: Attribute\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t422 [label=\"Data.GraphViz.Attributes\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t556 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Bool {\n\t\t\tgraph [label=\"Instance for: Bool\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1476 [label=\"Data.GraphViz.Printing\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=cyan];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_BrewerName {\n\t\t\tgraph [label=\"Instance for: BrewerName\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1220 [label=\"Data.GraphViz.Attributes.Colors\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Char {\n\t\t\tgraph [label=\"Instance for: Char\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1460 [label=\"Data.GraphViz.Printing\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1472 [label=\"Data.GraphViz.Printing\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1477 [label=\"Data.GraphViz.Printing\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=cyan];\n\t\t\t1486 [label=\"Data.GraphViz.Printing\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_ClusterMode {\n\t\t\tgraph [label=\"Instance for: ClusterMode\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t557 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Color {\n\t\t\tgraph [label=\"Instance for: Color\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1206 [label=\"Data.GraphViz.Attributes.Colors\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1218 [label=\"Data.GraphViz.Attributes.Colors\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1221 [label=\"Data.GraphViz.Attributes.Colors\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1224 [label=\"Data.GraphViz.Attributes.Colors\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_ColorScheme {\n\t\t\tgraph [label=\"Instance for: ColorScheme\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1222 [label=\"Data.GraphViz.Attributes.Colors\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_CompassPoint {\n\t\t\tgraph [label=\"Instance for: CompassPoint\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1366 [label=\"Data.GraphViz.Attributes.Internal\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_DEConstraints {\n\t\t\tgraph [label=\"Instance for: DEConstraints\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t558 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_DPoint {\n\t\t\tgraph [label=\"Instance for: DPoint\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t521 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t559 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_DirType {\n\t\t\tgraph [label=\"Instance for: DirType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t560 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Double {\n\t\t\tgraph [label=\"Instance for: Double\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1461 [label=\"Data.GraphViz.Printing\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1473 [label=\"Data.GraphViz.Printing\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1478 [label=\"Data.GraphViz.Printing\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=cyan];\n\t\t\t1487 [label=\"Data.GraphViz.Printing\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_EdgeType {\n\t\t\tgraph [label=\"Instance for: EdgeType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t522 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t561 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_FocusType {\n\t\t\tgraph [label=\"Instance for: FocusType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t523 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t562 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_GlobalAttributes {\n\t\t\tgraph [label=\"Instance for: GlobalAttributes\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1710 [label=\"Data.GraphViz.Types.Common\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1768 [label=\"Data.GraphViz.Types.Common\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1772 [label=\"Data.GraphViz.Types.Common\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_GraphID {\n\t\t\tgraph [label=\"Instance for: GraphID\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1761 [label=\"Data.GraphViz.Types.Common\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1769 [label=\"Data.GraphViz.Types.Common\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_HtmlAlign {\n\t\t\tgraph [label=\"Instance for: HtmlAlign\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1328 [label=\"Data.GraphViz.Attributes.HTML\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_HtmlAttribute {\n\t\t\tgraph [label=\"Instance for: HtmlAttribute\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1277 [label=\"Data.GraphViz.Attributes.HTML\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1329 [label=\"Data.GraphViz.Attributes.HTML\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1338 [label=\"Data.GraphViz.Attributes.HTML\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_HtmlCell {\n\t\t\tgraph [label=\"Instance for: HtmlCell\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1278 [label=\"Data.GraphViz.Attributes.HTML\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1330 [label=\"Data.GraphViz.Attributes.HTML\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1339 [label=\"Data.GraphViz.Attributes.HTML\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_HtmlImg {\n\t\t\tgraph [label=\"Instance for: HtmlImg\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1331 [label=\"Data.GraphViz.Attributes.HTML\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_HtmlLabel {\n\t\t\tgraph [label=\"Instance for: HtmlLabel\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1332 [label=\"Data.GraphViz.Attributes.HTML\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_HtmlRow {\n\t\t\tgraph [label=\"Instance for: HtmlRow\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1279 [label=\"Data.GraphViz.Attributes.HTML\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1333 [label=\"Data.GraphViz.Attributes.HTML\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1340 [label=\"Data.GraphViz.Attributes.HTML\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_HtmlScale {\n\t\t\tgraph [label=\"Instance for: HtmlScale\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1334 [label=\"Data.GraphViz.Attributes.HTML\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_HtmlTable {\n\t\t\tgraph [label=\"Instance for: HtmlTable\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1335 [label=\"Data.GraphViz.Attributes.HTML\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_HtmlTextItem {\n\t\t\tgraph [label=\"Instance for: HtmlTextItem\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1280 [label=\"Data.GraphViz.Attributes.HTML\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1336 [label=\"Data.GraphViz.Attributes.HTML\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1341 [label=\"Data.GraphViz.Attributes.HTML\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_HtmlVAlign {\n\t\t\tgraph [label=\"Instance for: HtmlVAlign\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1337 [label=\"Data.GraphViz.Attributes.HTML\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Int {\n\t\t\tgraph [label=\"Instance for: Int\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1479 [label=\"Data.GraphViz.Printing\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=cyan];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Justification {\n\t\t\tgraph [label=\"Instance for: Justification\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t563 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Label {\n\t\t\tgraph [label=\"Instance for: Label\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t524 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t564 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_LayerID {\n\t\t\tgraph [label=\"Instance for: LayerID\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t423 [label=\"Data.GraphViz.Attributes\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t525 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t565 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t594 [label=\"Data.GraphViz.Attributes\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_LayerList {\n\t\t\tgraph [label=\"Instance for: LayerList\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t526 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t566 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_LayerRange {\n\t\t\tgraph [label=\"Instance for: LayerRange\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t527 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t567 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_ModeType {\n\t\t\tgraph [label=\"Instance for: ModeType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t568 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Model {\n\t\t\tgraph [label=\"Instance for: Model\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t569 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_OutputMode {\n\t\t\tgraph [label=\"Instance for: OutputMode\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t570 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Overlap {\n\t\t\tgraph [label=\"Instance for: Overlap\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t571 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Pack {\n\t\t\tgraph [label=\"Instance for: Pack\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t572 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_PackMode {\n\t\t\tgraph [label=\"Instance for: PackMode\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t573 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_PageDir {\n\t\t\tgraph [label=\"Instance for: PageDir\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t574 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Point {\n\t\t\tgraph [label=\"Instance for: Point\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t424 [label=\"Data.GraphViz.Attributes\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t528 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t575 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t595 [label=\"Data.GraphViz.Attributes\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_PortName {\n\t\t\tgraph [label=\"Instance for: PortName\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1364 [label=\"Data.GraphViz.Attributes.Internal\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1367 [label=\"Data.GraphViz.Attributes.Internal\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_PortPos {\n\t\t\tgraph [label=\"Instance for: PortPos\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1365 [label=\"Data.GraphViz.Attributes.Internal\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1368 [label=\"Data.GraphViz.Attributes.Internal\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Pos {\n\t\t\tgraph [label=\"Instance for: Pos\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t529 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t576 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_QuadType {\n\t\t\tgraph [label=\"Instance for: QuadType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t577 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_RankDir {\n\t\t\tgraph [label=\"Instance for: RankDir\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t578 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_RankType {\n\t\t\tgraph [label=\"Instance for: RankType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t579 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Ratios {\n\t\t\tgraph [label=\"Instance for: Ratios\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t580 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_RecordField {\n\t\t\tgraph [label=\"Instance for: RecordField\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t425 [label=\"Data.GraphViz.Attributes\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t530 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t581 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t596 [label=\"Data.GraphViz.Attributes\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Rect {\n\t\t\tgraph [label=\"Instance for: Rect\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t531 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t582 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Root {\n\t\t\tgraph [label=\"Instance for: Root\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t532 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t583 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_STStyle {\n\t\t\tgraph [label=\"Instance for: STStyle\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t584 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_ScaleType {\n\t\t\tgraph [label=\"Instance for: ScaleType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t585 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Shape {\n\t\t\tgraph [label=\"Instance for: Shape\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t586 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_SmoothType {\n\t\t\tgraph [label=\"Instance for: SmoothType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t587 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Spline {\n\t\t\tgraph [label=\"Instance for: Spline\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t426 [label=\"Data.GraphViz.Attributes\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t533 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t588 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t597 [label=\"Data.GraphViz.Attributes\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_StartType {\n\t\t\tgraph [label=\"Instance for: StartType\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t589 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_StyleItem {\n\t\t\tgraph [label=\"Instance for: StyleItem\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t427 [label=\"Data.GraphViz.Attributes\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t534 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t590 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t598 [label=\"Data.GraphViz.Attributes\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_StyleName {\n\t\t\tgraph [label=\"Instance for: StyleName\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t535 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t591 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_VerticalPlacement {\n\t\t\tgraph [label=\"Instance for: VerticalPlacement\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t592 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_ViewPort {\n\t\t\tgraph [label=\"Instance for: ViewPort\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t536 [label=\"Data.GraphViz.Attributes\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t593 [label=\"Data.GraphViz.Attributes\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Word16 {\n\t\t\tgraph [label=\"Instance for: Word16\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1480 [label=\"Data.GraphViz.Printing\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=cyan];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_Word8 {\n\t\t\tgraph [label=\"Instance for: Word8\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1481 [label=\"Data.GraphViz.Printing\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=cyan];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_X11Color {\n\t\t\tgraph [label=\"Instance for: X11Color\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1223 [label=\"Data.GraphViz.Attributes.Colors\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_Class_PrintDot_Data_a {\n\t\t\tgraph [label=\"Instance for: [a]\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1474 [label=\"Data.GraphViz.Printing\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1482 [label=\"Data.GraphViz.Printing\\nunqtDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\tsubgraph cluster_DefaultInstance_PrintDot {\n\t\t\tgraph [label=\"Default Instance\",\n\t\t\t\tfillcolor=slategray1];\n\t\t\t1459 [label=\"Data.GraphViz.Printing\\nlistToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1471 [label=\"Data.GraphViz.Printing\\ntoDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t\t1485 [label=\"Data.GraphViz.Printing\\nunqtListToDot\", style=\"filled,solid\", shape=octagon, fillcolor=bisque];\n\t\t}\n\t\t1458 [label=\"Data.GraphViz.Printing\\nlistToDot\", style=\"filled,solid\", shape=doubleoctagon, fillcolor=goldenrod];\n\t\t1470 [label=\"Data.GraphViz.Printing\\ntoDot\", style=\"filled,solid\", shape=doubleoctagon, fillcolor=goldenrod];\n\t\t1475 [label=\"Data.GraphViz.Printing\\nunqtDot\", style=\"filled,solid\", shape=doubleoctagon, fillcolor=goldenrod];\n\t\t1484 [label=\"Data.GraphViz.Printing\\nunqtListToDot\", style=\"filled,solid\", shape=doubleoctagon, fillcolor=goldenrod];\n\t\t422 -> 1484 [penwidth=1, color=black];\n\t\t423 -> 1470 [penwidth=1, color=black];\n\t\t423 -> 1475 [penwidth=1, color=black];\n\t\t424 -> 1484 [penwidth=1, color=black];\n\t\t425 -> 1470 [penwidth=1, color=black];\n\t\t425 -> 1484 [penwidth=1, color=black];\n\t\t426 -> 1484 [penwidth=1, color=black];\n\t\t427 -> 1470 [penwidth=1, color=black];\n\t\t427 -> 1484 [penwidth=1, color=black];\n\t\t520 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t521 -> 1470 [penwidth=\"1.6931471805599454\", color=black];\n\t\t522 -> 1475 [penwidth=1, color=black];\n\t\t523 -> 1470 [penwidth=\"1.6931471805599454\", color=black];\n\t\t524 -> 1470 [penwidth=\"1.6931471805599454\", color=black];\n\t\t524 -> 1475 [penwidth=1, color=black];\n\t\t525 -> 1470 [penwidth=1, color=black];\n\t\t525 -> 1475 [penwidth=1, color=black];\n\t\t526 -> 1470 [penwidth=1, color=black];\n\t\t527 -> 1470 [penwidth=1, color=black];\n\t\t527 -> 1475 [penwidth=1, color=black];\n\t\t528 -> 1475 [penwidth=1, color=black];\n\t\t529 -> 1470 [penwidth=\"1.6931471805599454\", color=black];\n\t\t530 -> 1475 [penwidth=1, color=black];\n\t\t531 -> 1475 [penwidth=1, color=black];\n\t\t532 -> 1470 [penwidth=1, color=black];\n\t\t532 -> 1475 [penwidth=1, color=black];\n\t\t533 -> 1475 [penwidth=1, color=black];\n\t\t534 -> 1470 [penwidth=1, color=black];\n\t\t534 -> 1475 [penwidth=1, color=black];\n\t\t535 -> 1470 [penwidth=1, color=black];\n\t\t535 -> 1475 [penwidth=1, color=black];\n\t\t536 -> 1475 [penwidth=1, color=black];\n\t\t551 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t552 -> 1475 [penwidth=\"3.1972245773362196\", color=black];\n\t\t554 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t555 -> 1475 [penwidth=1, color=black];\n\t\t556 -> 1470 [penwidth=\"1.6931471805599454\", color=black];\n\t\t557 -> 1475 [penwidth=\"2.09861228866811\", color=black];\n\t\t558 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t559 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t560 -> 1475 [penwidth=\"2.386294361119891\", color=black];\n\t\t561 -> 1470 [penwidth=\"1.6931471805599454\", color=black];\n\t\t562 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t564 -> 1475 [penwidth=\"2.09861228866811\", color=black];\n\t\t565 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t566 -> 1475 [penwidth=1, color=black];\n\t\t567 -> 1475 [penwidth=\"2.386294361119891\", color=black];\n\t\t571 -> 1475 [penwidth=\"2.09861228866811\", color=black];\n\t\t572 -> 1475 [penwidth=\"2.09861228866811\", color=black];\n\t\t573 -> 1475 [penwidth=1, color=black];\n\t\t575 -> 1475 [penwidth=1, color=black];\n\t\t576 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t580 -> 1475 [penwidth=1, color=black];\n\t\t581 -> 1475 [penwidth=1, color=black];\n\t\t583 -> 1475 [penwidth=\"2.09861228866811\", color=black];\n\t\t585 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t588 -> 1475 [penwidth=1, color=black];\n\t\t589 -> 1475 [penwidth=\"2.386294361119891\", color=black];\n\t\t590 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t591 -> 1475 [penwidth=1, color=black];\n\t\t593 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t594 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t595 -> 1475 [penwidth=1, color=black];\n\t\t596 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t597 -> 1475 [penwidth=1, color=black];\n\t\t598 -> 1475 [penwidth=1, color=black];\n\t\t1206 -> 1470 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1206 -> 1484 [penwidth=1, color=black];\n\t\t1218 -> 1470 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1218 -> 1475 [penwidth=1, color=black];\n\t\t1220 -> 1475 [penwidth=\"4.555348061489413\", color=black];\n\t\t1221 -> 1475 [penwidth=\"2.09861228866811\", color=black];\n\t\t1222 -> 1475 [penwidth=\"2.09861228866811\", color=black];\n\t\t1223 -> 1475 [penwidth=\"7.302618975744905\", color=black];\n\t\t1224 -> 1475 [penwidth=1, color=black];\n\t\t1277 -> 1484 [penwidth=1, color=black];\n\t\t1278 -> 1484 [penwidth=1, color=black];\n\t\t1279 -> 1484 [penwidth=1, color=black];\n\t\t1280 -> 1484 [penwidth=1, color=black];\n\t\t1330 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1332 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1333 -> 1475 [penwidth=1, color=black];\n\t\t1335 -> 1470 [penwidth=1, color=black];\n\t\t1336 -> 1475 [penwidth=1, color=black];\n\t\t1338 -> 1475 [penwidth=1, color=black];\n\t\t1339 -> 1475 [penwidth=1, color=black];\n\t\t1340 -> 1475 [penwidth=1, color=black];\n\t\t1341 -> 1475 [penwidth=1, color=black];\n\t\t1364 -> 1470 [penwidth=1, color=black];\n\t\t1365 -> 1470 [penwidth=1, color=black];\n\t\t1365 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t\t1367 -> 1475 [penwidth=1, color=black];\n\t\t1368 -> 1475 [penwidth=\"2.09861228866811\", color=black];\n\t\t1458 -> 422 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 423 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1458 -> 424 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 425 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1458 -> 426 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 427 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1458 -> 1206 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1458 -> 1277 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 1278 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 1279 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 1280 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 1459 [penwidth=1, color=turquoise, dir=none];\n\t\t1458 -> 1460 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 1461 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1458 -> 1708 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 1709 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 1710 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 1797 [penwidth=1, color=navy, dir=none];\n\t\t1458 -> 1798 [penwidth=1, color=navy, dir=none];\n\t\t1459 -> 1484 [penwidth=1, color=black];\n\t\t1461 -> 1470 [penwidth=1, color=black];\n\t\t1461 -> 1484 [penwidth=1, color=black];\n\t\t1470 -> 520 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1470 -> 521 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1470 -> 522 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1470 -> 523 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1470 -> 524 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1470 -> 525 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1470 -> 526 [penwidth=1, color=navy, dir=none];\n\t\t1470 -> 527 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1470 -> 528 [penwidth=1, color=navy, dir=none];\n\t\t1470 -> 529 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1470 -> 530 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1470 -> 531 [penwidth=1, color=navy, dir=none];\n\t\t1470 -> 532 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1470 -> 533 [penwidth=1, color=navy, dir=none];\n\t\t1470 -> 534 [penwidth=1, color=navy, dir=none];\n\t\t1470 -> 535 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1470 -> 536 [penwidth=1, color=navy, dir=none];\n\t\t1470 -> 1218 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1470 -> 1364 [penwidth=1, color=navy, dir=none];\n\t\t1470 -> 1365 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1470 -> 1471 [penwidth=1, color=turquoise, dir=none];\n\t\t1470 -> 1472 [penwidth=1, color=navy, dir=none];\n\t\t1470 -> 1473 [penwidth=1, color=navy, dir=none];\n\t\t1470 -> 1474 [penwidth=1, color=navy, dir=none];\n\t\t1470 -> 1761 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1471 -> 1475 [penwidth=1, color=black];\n\t\t1473 -> 1475 [penwidth=1, color=black];\n\t\t1474 -> 1458 [penwidth=1, color=chartreuse];\n\t\t1475 -> 550 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1475 -> 551 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 552 [penwidth=\"3.1972245773362196\", color=navy, dir=none];\n\t\t1475 -> 553 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 554 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 555 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1475 -> 556 [penwidth=\"5.976733742420574\", color=navy, dir=none];\n\t\t1475 -> 557 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 558 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 559 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1475 -> 560 [penwidth=\"2.386294361119891\", color=navy, dir=none];\n\t\t1475 -> 561 [penwidth=\"2.6094379124341005\", color=navy, dir=none];\n\t\t1475 -> 562 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1475 -> 563 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 564 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 565 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 566 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 567 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1475 -> 568 [penwidth=\"2.386294361119891\", color=navy, dir=none];\n\t\t1475 -> 569 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 570 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 571 [penwidth=\"3.0794415416798357\", color=navy, dir=none];\n\t\t1475 -> 572 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 573 [penwidth=\"2.386294361119891\", color=navy, dir=none];\n\t\t1475 -> 574 [penwidth=\"3.0794415416798357\", color=navy, dir=none];\n\t\t1475 -> 575 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 576 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1475 -> 577 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 578 [penwidth=\"2.386294361119891\", color=navy, dir=none];\n\t\t1475 -> 579 [penwidth=\"2.6094379124341005\", color=navy, dir=none];\n\t\t1475 -> 580 [penwidth=\"2.6094379124341005\", color=navy, dir=none];\n\t\t1475 -> 581 [penwidth=\"2.386294361119891\", color=navy, dir=none];\n\t\t1475 -> 582 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 583 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 584 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 585 [penwidth=\"2.6094379124341005\", color=navy, dir=none];\n\t\t1475 -> 586 [penwidth=\"4.465735902799727\", color=navy, dir=none];\n\t\t1475 -> 587 [penwidth=\"2.9459101490553135\", color=navy, dir=none];\n\t\t1475 -> 588 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 589 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 590 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 591 [penwidth=\"3.1972245773362196\", color=navy, dir=none];\n\t\t1475 -> 592 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 593 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1220 [penwidth=\"4.555348061489413\", color=navy, dir=none];\n\t\t1475 -> 1221 [penwidth=\"2.6094379124341005\", color=navy, dir=none];\n\t\t1475 -> 1222 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1475 -> 1223 [penwidth=\"7.302618975744905\", color=navy, dir=none];\n\t\t1475 -> 1328 [penwidth=\"2.386294361119891\", color=navy, dir=none];\n\t\t1475 -> 1329 [penwidth=\"4.091042453358316\", color=navy, dir=none];\n\t\t1475 -> 1330 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1475 -> 1331 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1332 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1475 -> 1333 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1334 [penwidth=\"2.6094379124341005\", color=navy, dir=none];\n\t\t1475 -> 1335 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1336 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 1337 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 1366 [penwidth=\"3.302585092994046\", color=navy, dir=none];\n\t\t1475 -> 1367 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1368 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1475 -> 1476 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1475 -> 1477 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1478 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1479 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1480 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1481 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1482 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1766 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1767 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1768 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1769 [penwidth=\"2.09861228866811\", color=navy, dir=none];\n\t\t1475 -> 1821 [penwidth=1, color=navy, dir=none];\n\t\t1475 -> 1822 [penwidth=\"2.386294361119891\", color=navy, dir=none];\n\t\t1475 -> 1823 [penwidth=1, color=navy, dir=none];\n\t\t1482 -> 1484 [penwidth=1, color=black];\n\t\t1484 -> 594 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 595 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 596 [penwidth=\"1.6931471805599454\", color=navy, dir=none];\n\t\t1484 -> 597 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 598 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1224 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1338 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1339 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1340 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1341 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1485 [penwidth=1, color=turquoise, dir=none];\n\t\t1484 -> 1486 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1487 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1770 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1771 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1772 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1824 [penwidth=1, color=navy, dir=none];\n\t\t1484 -> 1825 [penwidth=1, color=navy, dir=none];\n\t\t1485 -> 1475 [penwidth=1, color=black];\n\t\t1487 -> 1475 [penwidth=1, color=black];\n\t\t1708 -> 1484 [penwidth=1, color=black];\n\t\t1709 -> 1484 [penwidth=1, color=black];\n\t\t1710 -> 1484 [penwidth=1, color=black];\n\t\t1761 -> 1470 [penwidth=1, color=black];\n\t\t1761 -> 1475 [penwidth=1, color=black];\n\t\t1768 -> 1470 [penwidth=1, color=black];\n\t\t1769 -> 1475 [penwidth=\"2.09861228866811\", color=black];\n\t\t1797 -> 1484 [penwidth=1, color=black];\n\t\t1798 -> 1484 [penwidth=1, color=black];\n\t\t1822 -> 1475 [penwidth=\"2.386294361119891\", color=black];\n\t\t1824 -> 1475 [penwidth=1, color=black];\n\t}\n\tsubgraph cluster_Data_ArrowFill {\n\t\tgraph [label=\"Data: ArrowFill\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t159 [label=\"Data.GraphViz.Attributes\\nFilledArrow\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t275 [label=\"Data.GraphViz.Attributes\\nOpenArrow\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_ArrowModifier {\n\t\tgraph [label=\"Data: ArrowModifier\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t84 [label=\"Data.GraphViz.Attributes\\nArrMod\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t402 [label=\"Data.GraphViz.Attributes\\narrowFill\", style=\"filled,solid\", shape=component, fillcolor=gold];\n\t\t403 [label=\"Data.GraphViz.Attributes\\narrowSide\", style=\"filled,solid\", shape=component, fillcolor=gold];\n\t\t402 -> 84 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t403 -> 84 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_ArrowShape {\n\t\tgraph [label=\"Data: ArrowShape\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t99 [label=\"Data.GraphViz.Attributes\\nBox\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t119 [label=\"Data.GraphViz.Attributes\\nCrow\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t128 [label=\"Data.GraphViz.Attributes\\nDiamond\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t137 [label=\"Data.GraphViz.Attributes\\nDotArrow\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t191 [label=\"Data.GraphViz.Attributes\\nInv\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t254 [label=\"Data.GraphViz.Attributes\\nNoArrow\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t267 [label=\"Data.GraphViz.Attributes\\nNormal\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t377 [label=\"Data.GraphViz.Attributes\\nTee\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t393 [label=\"Data.GraphViz.Attributes\\nVee\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_ArrowSide {\n\t\tgraph [label=\"Data: ArrowSide\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t98 [label=\"Data.GraphViz.Attributes\\nBothSides\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t232 [label=\"Data.GraphViz.Attributes\\nLeftSide\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t328 [label=\"Data.GraphViz.Attributes\\nRightSide\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_ArrowType {\n\t\tgraph [label=\"Data: ArrowType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t82 [label=\"Data.GraphViz.Attributes\\nAType\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_AspectType {\n\t\tgraph [label=\"Data: AspectType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t316 [label=\"Data.GraphViz.Attributes\\nRatioOnly\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t317 [label=\"Data.GraphViz.Attributes\\nRatioPassCount\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Attribute {\n\t\tgraph [label=\"Data: Attribute\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t31 [label=\"Data.GraphViz.AttributeGenerator\\nA\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t\t48 [label=\"Data.GraphViz.AttributeGenerator\\ncnst\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t49 [label=\"Data.GraphViz.AttributeGenerator\\ncomment\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t57 [label=\"Data.GraphViz.AttributeGenerator\\nforClusters\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t58 [label=\"Data.GraphViz.AttributeGenerator\\nforEdges\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t59 [label=\"Data.GraphViz.AttributeGenerator\\nforGraphs\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t60 [label=\"Data.GraphViz.AttributeGenerator\\nforNodes\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t61 [label=\"Data.GraphViz.AttributeGenerator\\nforSubGraphs\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t66 [label=\"Data.GraphViz.AttributeGenerator\\nname\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t67 [label=\"Data.GraphViz.AttributeGenerator\\nparseDef\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t69 [label=\"Data.GraphViz.AttributeGenerator\\nparseNames\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t77 [label=\"Data.GraphViz.AttributeGenerator\\nvaltype\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t85 [label=\"Data.GraphViz.Attributes\\nArrowHead\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t86 [label=\"Data.GraphViz.Attributes\\nArrowSize\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t87 [label=\"Data.GraphViz.Attributes\\nArrowTail\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t88 [label=\"Data.GraphViz.Attributes\\nAspect\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t93 [label=\"Data.GraphViz.Attributes\\nBb\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t94 [label=\"Data.GraphViz.Attributes\\nBgColor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t104 [label=\"Data.GraphViz.Attributes\\nCenter\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t105 [label=\"Data.GraphViz.Attributes\\nCharset\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t108 [label=\"Data.GraphViz.Attributes\\nClusterRank\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t109 [label=\"Data.GraphViz.Attributes\\nColor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t110 [label=\"Data.GraphViz.Attributes\\nColorScheme\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t111 [label=\"Data.GraphViz.Attributes\\nComment\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t113 [label=\"Data.GraphViz.Attributes\\nCompound\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t117 [label=\"Data.GraphViz.Attributes\\nConcentrate\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t118 [label=\"Data.GraphViz.Attributes\\nConstraint\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t121 [label=\"Data.GraphViz.Attributes\\nDPI\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t123 [label=\"Data.GraphViz.Attributes\\nDamping\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t125 [label=\"Data.GraphViz.Attributes\\nDecorate\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t126 [label=\"Data.GraphViz.Attributes\\nDefaultDist\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t130 [label=\"Data.GraphViz.Attributes\\nDim\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t131 [label=\"Data.GraphViz.Attributes\\nDimen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t132 [label=\"Data.GraphViz.Attributes\\nDir\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t133 [label=\"Data.GraphViz.Attributes\\nDirEdgeConstraints\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t134 [label=\"Data.GraphViz.Attributes\\nDistortion\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t141 [label=\"Data.GraphViz.Attributes\\nESep\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t143 [label=\"Data.GraphViz.Attributes\\nEdgeTarget\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t144 [label=\"Data.GraphViz.Attributes\\nEdgeTooltip\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t145 [label=\"Data.GraphViz.Attributes\\nEdgeURL\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t149 [label=\"Data.GraphViz.Attributes\\nEpsilon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t154 [label=\"Data.GraphViz.Attributes\\nFillColor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t160 [label=\"Data.GraphViz.Attributes\\nFixedSize\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t163 [label=\"Data.GraphViz.Attributes\\nFontColor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t164 [label=\"Data.GraphViz.Attributes\\nFontName\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t165 [label=\"Data.GraphViz.Attributes\\nFontNames\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t166 [label=\"Data.GraphViz.Attributes\\nFontPath\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t167 [label=\"Data.GraphViz.Attributes\\nFontSize\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t175 [label=\"Data.GraphViz.Attributes\\nGroup\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t176 [label=\"Data.GraphViz.Attributes\\nHeadClip\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t177 [label=\"Data.GraphViz.Attributes\\nHeadLabel\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t178 [label=\"Data.GraphViz.Attributes\\nHeadPort\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t179 [label=\"Data.GraphViz.Attributes\\nHeadTarget\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t180 [label=\"Data.GraphViz.Attributes\\nHeadTooltip\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t181 [label=\"Data.GraphViz.Attributes\\nHeadURL\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t182 [label=\"Data.GraphViz.Attributes\\nHeight\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t188 [label=\"Data.GraphViz.Attributes\\nID\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t189 [label=\"Data.GraphViz.Attributes\\nImage\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t190 [label=\"Data.GraphViz.Attributes\\nImageScale\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t202 [label=\"Data.GraphViz.Attributes\\nK\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t205 [label=\"Data.GraphViz.Attributes\\nLHead\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t207 [label=\"Data.GraphViz.Attributes\\nLPos\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t212 [label=\"Data.GraphViz.Attributes\\nLTail\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t213 [label=\"Data.GraphViz.Attributes\\nLabel\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t214 [label=\"Data.GraphViz.Attributes\\nLabelAngle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t215 [label=\"Data.GraphViz.Attributes\\nLabelDistance\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t216 [label=\"Data.GraphViz.Attributes\\nLabelFloat\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t217 [label=\"Data.GraphViz.Attributes\\nLabelFontColor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t218 [label=\"Data.GraphViz.Attributes\\nLabelFontName\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t219 [label=\"Data.GraphViz.Attributes\\nLabelFontSize\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t220 [label=\"Data.GraphViz.Attributes\\nLabelJust\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t221 [label=\"Data.GraphViz.Attributes\\nLabelLoc\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t222 [label=\"Data.GraphViz.Attributes\\nLabelTarget\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t223 [label=\"Data.GraphViz.Attributes\\nLabelTooltip\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t224 [label=\"Data.GraphViz.Attributes\\nLabelURL\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t226 [label=\"Data.GraphViz.Attributes\\nLandscape\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t227 [label=\"Data.GraphViz.Attributes\\nLayer\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t228 [label=\"Data.GraphViz.Attributes\\nLayerSep\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t229 [label=\"Data.GraphViz.Attributes\\nLayers\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t230 [label=\"Data.GraphViz.Attributes\\nLayout\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t233 [label=\"Data.GraphViz.Attributes\\nLen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t234 [label=\"Data.GraphViz.Attributes\\nLevels\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t235 [label=\"Data.GraphViz.Attributes\\nLevelsGap\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t239 [label=\"Data.GraphViz.Attributes\\nMCLimit\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t245 [label=\"Data.GraphViz.Attributes\\nMargin\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t246 [label=\"Data.GraphViz.Attributes\\nMaxIter\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t248 [label=\"Data.GraphViz.Attributes\\nMinDist\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t249 [label=\"Data.GraphViz.Attributes\\nMinLen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t251 [label=\"Data.GraphViz.Attributes\\nMode\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t252 [label=\"Data.GraphViz.Attributes\\nModel\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t253 [label=\"Data.GraphViz.Attributes\\nMosek\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t259 [label=\"Data.GraphViz.Attributes\\nNoJustify\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t265 [label=\"Data.GraphViz.Attributes\\nNodeSep\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t269 [label=\"Data.GraphViz.Attributes\\nNormalize\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t272 [label=\"Data.GraphViz.Attributes\\nNslimit\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t273 [label=\"Data.GraphViz.Attributes\\nNslimit1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t276 [label=\"Data.GraphViz.Attributes\\nOrdering\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t277 [label=\"Data.GraphViz.Attributes\\nOrientation\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t278 [label=\"Data.GraphViz.Attributes\\nOutputOrder\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t279 [label=\"Data.GraphViz.Attributes\\nOverlap\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t280 [label=\"Data.GraphViz.Attributes\\nOverlapScaling\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t282 [label=\"Data.GraphViz.Attributes\\nPack\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t287 [label=\"Data.GraphViz.Attributes\\nPackMode\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t289 [label=\"Data.GraphViz.Attributes\\nPad\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t290 [label=\"Data.GraphViz.Attributes\\nPage\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t291 [label=\"Data.GraphViz.Attributes\\nPageDir\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t293 [label=\"Data.GraphViz.Attributes\\nPenColor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t294 [label=\"Data.GraphViz.Attributes\\nPenWidth\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t296 [label=\"Data.GraphViz.Attributes\\nPeripheries\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t297 [label=\"Data.GraphViz.Attributes\\nPin\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t305 [label=\"Data.GraphViz.Attributes\\nPos\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t308 [label=\"Data.GraphViz.Attributes\\nQuadTree\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t309 [label=\"Data.GraphViz.Attributes\\nQuantum\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t312 [label=\"Data.GraphViz.Attributes\\nRank\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t313 [label=\"Data.GraphViz.Attributes\\nRankDir\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t314 [label=\"Data.GraphViz.Attributes\\nRankSep\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t315 [label=\"Data.GraphViz.Attributes\\nRatio\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t319 [label=\"Data.GraphViz.Attributes\\nReMinCross\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t323 [label=\"Data.GraphViz.Attributes\\nRects\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t324 [label=\"Data.GraphViz.Attributes\\nRegular\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t327 [label=\"Data.GraphViz.Attributes\\nRepulsiveForce\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t329 [label=\"Data.GraphViz.Attributes\\nRoot\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t330 [label=\"Data.GraphViz.Attributes\\nRotate\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t334 [label=\"Data.GraphViz.Attributes\\nSameHead\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t336 [label=\"Data.GraphViz.Attributes\\nSameTail\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t337 [label=\"Data.GraphViz.Attributes\\nSamplePoints\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t340 [label=\"Data.GraphViz.Attributes\\nSearchSize\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t342 [label=\"Data.GraphViz.Attributes\\nSep\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t344 [label=\"Data.GraphViz.Attributes\\nShape\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t345 [label=\"Data.GraphViz.Attributes\\nShapeFile\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t347 [label=\"Data.GraphViz.Attributes\\nShowBoxes\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t348 [label=\"Data.GraphViz.Attributes\\nSides\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t350 [label=\"Data.GraphViz.Attributes\\nSize\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t351 [label=\"Data.GraphViz.Attributes\\nSkew\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t352 [label=\"Data.GraphViz.Attributes\\nSmoothing\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t354 [label=\"Data.GraphViz.Attributes\\nSortV\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t359 [label=\"Data.GraphViz.Attributes\\nSplines\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t361 [label=\"Data.GraphViz.Attributes\\nStart\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t366 [label=\"Data.GraphViz.Attributes\\nStyle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t367 [label=\"Data.GraphViz.Attributes\\nStyleSheet\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t370 [label=\"Data.GraphViz.Attributes\\nTailClip\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t371 [label=\"Data.GraphViz.Attributes\\nTailLabel\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t372 [label=\"Data.GraphViz.Attributes\\nTailPort\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t373 [label=\"Data.GraphViz.Attributes\\nTailTarget\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t374 [label=\"Data.GraphViz.Attributes\\nTailTooltip\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t375 [label=\"Data.GraphViz.Attributes\\nTailURL\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t376 [label=\"Data.GraphViz.Attributes\\nTarget\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t379 [label=\"Data.GraphViz.Attributes\\nTooltip\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t385 [label=\"Data.GraphViz.Attributes\\nTrueColor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t386 [label=\"Data.GraphViz.Attributes\\nURL\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t388 [label=\"Data.GraphViz.Attributes\\nUnknownAttribute\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t394 [label=\"Data.GraphViz.Attributes\\nVertices\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t395 [label=\"Data.GraphViz.Attributes\\nViewPort\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t396 [label=\"Data.GraphViz.Attributes\\nVoroMargin\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t398 [label=\"Data.GraphViz.Attributes\\nWeight\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t399 [label=\"Data.GraphViz.Attributes\\nWidth\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t401 [label=\"Data.GraphViz.Attributes\\nZ\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t48 -> 31 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t49 -> 31 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t57 -> 31 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t58 -> 31 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t59 -> 31 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t60 -> 31 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t61 -> 31 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t66 -> 31 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t67 -> 31 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t69 -> 31 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t77 -> 31 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_Atts {\n\t\tgraph [label=\"Data: Atts\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t32 [label=\"Data.GraphViz.AttributeGenerator\\nAS\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t\t46 [label=\"Data.GraphViz.AttributeGenerator\\natts\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t74 [label=\"Data.GraphViz.AttributeGenerator\\ntpNm\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t46 -> 32 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t74 -> 32 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_BrewerName {\n\t\tgraph [label=\"Data: BrewerName\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t611 [label=\"Data.GraphViz.Attributes.Colors\\nAccent\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t642 [label=\"Data.GraphViz.Attributes.Colors\\nBlues\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t643 [label=\"Data.GraphViz.Attributes.Colors\\nBrbg\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t651 [label=\"Data.GraphViz.Attributes.Colors\\nBugn\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t652 [label=\"Data.GraphViz.Attributes.Colors\\nBupu\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t690 [label=\"Data.GraphViz.Attributes.Colors\\nDark2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t752 [label=\"Data.GraphViz.Attributes.Colors\\nGnbu\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t871 [label=\"Data.GraphViz.Attributes.Colors\\nGreens\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t872 [label=\"Data.GraphViz.Attributes.Colors\\nGreys\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1018 [label=\"Data.GraphViz.Attributes.Colors\\nOranges\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1024 [label=\"Data.GraphViz.Attributes.Colors\\nOrrd\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1025 [label=\"Data.GraphViz.Attributes.Colors\\nPaired\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1043 [label=\"Data.GraphViz.Attributes.Colors\\nPastel1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1044 [label=\"Data.GraphViz.Attributes.Colors\\nPastel2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1056 [label=\"Data.GraphViz.Attributes.Colors\\nPiyg\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1063 [label=\"Data.GraphViz.Attributes.Colors\\nPrgn\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1064 [label=\"Data.GraphViz.Attributes.Colors\\nPubu\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1065 [label=\"Data.GraphViz.Attributes.Colors\\nPubugn\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1066 [label=\"Data.GraphViz.Attributes.Colors\\nPuor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1067 [label=\"Data.GraphViz.Attributes.Colors\\nPurd\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1073 [label=\"Data.GraphViz.Attributes.Colors\\nPurples\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1076 [label=\"Data.GraphViz.Attributes.Colors\\nRdbu\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1077 [label=\"Data.GraphViz.Attributes.Colors\\nRdgy\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1078 [label=\"Data.GraphViz.Attributes.Colors\\nRdpu\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1079 [label=\"Data.GraphViz.Attributes.Colors\\nRdylbu\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1080 [label=\"Data.GraphViz.Attributes.Colors\\nRdylgn\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1086 [label=\"Data.GraphViz.Attributes.Colors\\nReds\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1114 [label=\"Data.GraphViz.Attributes.Colors\\nSet1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1115 [label=\"Data.GraphViz.Attributes.Colors\\nSet2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1116 [label=\"Data.GraphViz.Attributes.Colors\\nSet3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1142 [label=\"Data.GraphViz.Attributes.Colors\\nSpectral\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1195 [label=\"Data.GraphViz.Attributes.Colors\\nYlgn\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1196 [label=\"Data.GraphViz.Attributes.Colors\\nYlgnbu\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1197 [label=\"Data.GraphViz.Attributes.Colors\\nYlorbr\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1198 [label=\"Data.GraphViz.Attributes.Colors\\nYlorrd\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_ClusterMode {\n\t\tgraph [label=\"Data: ClusterMode\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t173 [label=\"Data.GraphViz.Attributes\\nGlobal\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t237 [label=\"Data.GraphViz.Attributes\\nLocal\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t255 [label=\"Data.GraphViz.Attributes\\nNoCluster\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_ClusterTree {\n\t\tgraph [label=\"Data: ClusterTree\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1668 [label=\"Data.GraphViz.Types.Clustering\\nCT\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1670 [label=\"Data.GraphViz.Types.Clustering\\nNT\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t}\n\tsubgraph cluster_Data_Color {\n\t\tgraph [label=\"Data: Color\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t644 [label=\"Data.GraphViz.Attributes.Colors\\nBrewerColor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t873 [label=\"Data.GraphViz.Attributes.Colors\\nHSV\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1074 [label=\"Data.GraphViz.Attributes.Colors\\nRGB\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1075 [label=\"Data.GraphViz.Attributes.Colors\\nRGBA\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1188 [label=\"Data.GraphViz.Attributes.Colors\\nX11Color\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1199 [label=\"Data.GraphViz.Attributes.Colors\\nalpha\", style=\"filled,solid\", shape=component, fillcolor=gold];\n\t\t1200 [label=\"Data.GraphViz.Attributes.Colors\\nblue\", style=\"filled,solid\", shape=component, fillcolor=gold];\n\t\t1203 [label=\"Data.GraphViz.Attributes.Colors\\ngreen\", style=\"filled,solid\", shape=component, fillcolor=gold];\n\t\t1205 [label=\"Data.GraphViz.Attributes.Colors\\nhue\", style=\"filled,solid\", shape=component, fillcolor=gold];\n\t\t1215 [label=\"Data.GraphViz.Attributes.Colors\\nred\", style=\"filled,solid\", shape=component, fillcolor=gold];\n\t\t1216 [label=\"Data.GraphViz.Attributes.Colors\\nsaturation\", style=\"filled,solid\", shape=component, fillcolor=gold];\n\t\t1225 [label=\"Data.GraphViz.Attributes.Colors\\nvalue\", style=\"filled,solid\", shape=component, fillcolor=gold];\n\t\t1199 -> 1075 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1200 -> 1074 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1200 -> 1075 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1203 -> 1074 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1203 -> 1075 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1205 -> 873 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1215 -> 1074 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1215 -> 1075 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1216 -> 873 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1225 -> 873 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_ColorScheme {\n\t\tgraph [label=\"Data: ColorScheme\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t645 [label=\"Data.GraphViz.Attributes.Colors\\nBrewerScheme\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1187 [label=\"Data.GraphViz.Attributes.Colors\\nX11\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_CompassPoint {\n\t\tgraph [label=\"Data: CompassPoint\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1342 [label=\"Data.GraphViz.Attributes.Internal\\nCenterPoint\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1344 [label=\"Data.GraphViz.Attributes.Internal\\nEast\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1346 [label=\"Data.GraphViz.Attributes.Internal\\nNoCP\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1347 [label=\"Data.GraphViz.Attributes.Internal\\nNorth\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1348 [label=\"Data.GraphViz.Attributes.Internal\\nNorthEast\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1349 [label=\"Data.GraphViz.Attributes.Internal\\nNorthWest\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1351 [label=\"Data.GraphViz.Attributes.Internal\\nSouth\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1352 [label=\"Data.GraphViz.Attributes.Internal\\nSouthEast\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1353 [label=\"Data.GraphViz.Attributes.Internal\\nSouthWest\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1354 [label=\"Data.GraphViz.Attributes.Internal\\nWest\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t}\n\tsubgraph cluster_Data_DEConstraints {\n\t\tgraph [label=\"Data: DEConstraints\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t142 [label=\"Data.GraphViz.Attributes\\nEdgeConstraints\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t185 [label=\"Data.GraphViz.Attributes\\nHierConstraints\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t256 [label=\"Data.GraphViz.Attributes\\nNoConstraints\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_DPoint {\n\t\tgraph [label=\"Data: DPoint\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t122 [label=\"Data.GraphViz.Attributes\\nDVal\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t281 [label=\"Data.GraphViz.Attributes\\nPVal\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_DirType {\n\t\tgraph [label=\"Data: DirType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t92 [label=\"Data.GraphViz.Attributes\\nBack\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t97 [label=\"Data.GraphViz.Attributes\\nBoth\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t168 [label=\"Data.GraphViz.Attributes\\nForward\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t257 [label=\"Data.GraphViz.Attributes\\nNoDir\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_DotEdge {\n\t\tgraph [label=\"Data: DotEdge\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1680 [label=\"Data.GraphViz.Types.Common\\nDotEdge\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1699 [label=\"Data.GraphViz.Types.Common\\ndirectedEdge\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1700 [label=\"Data.GraphViz.Types.Common\\nedgeAttributes\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1701 [label=\"Data.GraphViz.Types.Common\\nedgeFromNodeID\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1702 [label=\"Data.GraphViz.Types.Common\\nedgeToNodeID\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1699 -> 1680 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1700 -> 1680 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1701 -> 1680 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1702 -> 1680 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_DotError {\n\t\tgraph [label=\"Data: DotError\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1683 [label=\"Data.GraphViz.Types.Common\\nEdgeError\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t\t1685 [label=\"Data.GraphViz.Types.Common\\nGraphError\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t\t1688 [label=\"Data.GraphViz.Types.Common\\nNodeError\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t}\n\tsubgraph cluster_Data_DotNode {\n\t\tgraph [label=\"Data: DotNode\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1681 [label=\"Data.GraphViz.Types.Common\\nDotNode\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1713 [label=\"Data.GraphViz.Types.Common\\nnodeAttributes\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1714 [label=\"Data.GraphViz.Types.Common\\nnodeID\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1713 -> 1681 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1714 -> 1681 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_EdgeID {\n\t\tgraph [label=\"Data: EdgeID\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1 [label=\"Data.GraphViz\\nEID\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t13 [label=\"Data.GraphViz\\neID\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t14 [label=\"Data.GraphViz\\neLbl\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t13 -> 1 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t14 -> 1 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_EdgeType {\n\t\tgraph [label=\"Data: EdgeType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t114 [label=\"Data.GraphViz.Attributes\\nCompoundEdge\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t236 [label=\"Data.GraphViz.Attributes\\nLineEdges\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t258 [label=\"Data.GraphViz.Attributes\\nNoEdges\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t302 [label=\"Data.GraphViz.Attributes\\nPolyLine\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t357 [label=\"Data.GraphViz.Attributes\\nSplineEdges\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_FocusType {\n\t\tgraph [label=\"Data: FocusType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t263 [label=\"Data.GraphViz.Attributes\\nNodeFocus\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t400 [label=\"Data.GraphViz.Attributes\\nXY\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_GDotGraph {\n\t\tgraph [label=\"Data: GDotGraph\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1776 [label=\"Data.GraphViz.Types.Generalised\\nGDotGraph\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1783 [label=\"Data.GraphViz.Types.Generalised\\ngDirectedGraph\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t1784 [label=\"Data.GraphViz.Types.Generalised\\ngGraphID\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t1785 [label=\"Data.GraphViz.Types.Generalised\\ngGraphStatements\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t1787 [label=\"Data.GraphViz.Types.Generalised\\ngStrictGraph\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t1783 -> 1776 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1784 -> 1776 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1785 -> 1776 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1787 -> 1776 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_GDotStatement {\n\t\tgraph [label=\"Data: GDotStatement\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1773 [label=\"Data.GraphViz.Types.Generalised\\nDE\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1774 [label=\"Data.GraphViz.Types.Generalised\\nDN\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1775 [label=\"Data.GraphViz.Types.Generalised\\nGA\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1778 [label=\"Data.GraphViz.Types.Generalised\\nSG\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_GDotSubGraph {\n\t\tgraph [label=\"Data: GDotSubGraph\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1777 [label=\"Data.GraphViz.Types.Generalised\\nGDotSG\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1786 [label=\"Data.GraphViz.Types.Generalised\\ngIsCluster\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t1788 [label=\"Data.GraphViz.Types.Generalised\\ngSubGraphID\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t1789 [label=\"Data.GraphViz.Types.Generalised\\ngSubGraphStmts\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t1786 -> 1777 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1788 -> 1777 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1789 -> 1777 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_GlobalAttributes {\n\t\tgraph [label=\"Data: GlobalAttributes\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1682 [label=\"Data.GraphViz.Types.Common\\nEdgeAttrs\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1684 [label=\"Data.GraphViz.Types.Common\\nGraphAttrs\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1687 [label=\"Data.GraphViz.Types.Common\\nNodeAttrs\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1691 [label=\"Data.GraphViz.Types.Common\\nattrs\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1691 -> 1682 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1691 -> 1684 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1691 -> 1687 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_GraphID {\n\t\tgraph [label=\"Data: GraphID\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1679 [label=\"Data.GraphViz.Types.Common\\nDbl\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1686 [label=\"Data.GraphViz.Types.Common\\nInt\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1689 [label=\"Data.GraphViz.Types.Common\\nStr\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t}\n\tsubgraph cluster_Data_GraphvizParams {\n\t\tgraph [label=\"Data: GraphvizParams\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t2 [label=\"Data.GraphViz\\nParams\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t7 [label=\"Data.GraphViz\\nclusterBy\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t8 [label=\"Data.GraphViz\\nclusterID\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t15 [label=\"Data.GraphViz\\nfmtCluster\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t16 [label=\"Data.GraphViz\\nfmtEdge\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t17 [label=\"Data.GraphViz\\nfmtNode\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t19 [label=\"Data.GraphViz\\nglobalAttributes\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t22 [label=\"Data.GraphViz\\nisDirected\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t7 -> 2 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t8 -> 2 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t15 -> 2 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t16 -> 2 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t17 -> 2 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t19 -> 2 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t22 -> 2 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_HtmlAlign {\n\t\tgraph [label=\"Data: HtmlAlign\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1229 [label=\"Data.GraphViz.Attributes.HTML\\nHCenter\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1230 [label=\"Data.GraphViz.Attributes.HTML\\nHLeft\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1232 [label=\"Data.GraphViz.Attributes.HTML\\nHRight\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1234 [label=\"Data.GraphViz.Attributes.HTML\\nHText\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_HtmlAttribute {\n\t\tgraph [label=\"Data: HtmlAttribute\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1236 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlAlign\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1237 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlBAlign\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1238 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlBGColor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1239 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlBorder\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1240 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlCellBorder\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1241 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlCellPadding\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1242 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlCellSpacing\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1243 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlColSpan\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1244 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlColor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1248 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlFace\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1249 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlFixedSize\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1251 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlHRef\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1252 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlHeight\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1258 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlPointSize\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1259 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlPort\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1261 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlRowSpan\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1262 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlScale\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1264 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlSrc\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1267 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlTarget\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1269 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlTitle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1270 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlVAlign\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1271 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlWidth\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_HtmlCell {\n\t\tgraph [label=\"Data: HtmlCell\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1254 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlImgCell\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1255 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlLabelCell\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_HtmlImg {\n\t\tgraph [label=\"Data: HtmlImg\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1253 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlImg\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_HtmlLabel {\n\t\tgraph [label=\"Data: HtmlLabel\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1266 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlTable\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1268 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlText\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_HtmlRow {\n\t\tgraph [label=\"Data: HtmlRow\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1260 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlRow\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_HtmlScale {\n\t\tgraph [label=\"Data: HtmlScale\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1245 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlExpandBoth\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1246 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlExpandHeight\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1247 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlExpandWidth\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1256 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlNaturalSize\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1263 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlScaleUniformly\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_HtmlTable {\n\t\tgraph [label=\"Data: HtmlTable\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1233 [label=\"Data.GraphViz.Attributes.HTML\\nHTable\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1322 [label=\"Data.GraphViz.Attributes.HTML\\ntableAttrs\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t1323 [label=\"Data.GraphViz.Attributes.HTML\\ntableFontAttrs\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t1324 [label=\"Data.GraphViz.Attributes.HTML\\ntableRows\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t1322 -> 1233 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1323 -> 1233 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1324 -> 1233 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_HtmlTextItem {\n\t\tgraph [label=\"Data: HtmlTextItem\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1250 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlFont\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1257 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlNewline\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1265 [label=\"Data.GraphViz.Attributes.HTML\\nHtmlStr\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_HtmlVAlign {\n\t\tgraph [label=\"Data: HtmlVAlign\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1228 [label=\"Data.GraphViz.Attributes.HTML\\nHBottom\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1231 [label=\"Data.GraphViz.Attributes.HTML\\nHMiddle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1235 [label=\"Data.GraphViz.Attributes.HTML\\nHTop\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Justification {\n\t\tgraph [label=\"Data: Justification\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t199 [label=\"Data.GraphViz.Attributes\\nJCenter\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t200 [label=\"Data.GraphViz.Attributes\\nJLeft\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t201 [label=\"Data.GraphViz.Attributes\\nJRight\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Label {\n\t\tgraph [label=\"Data: Label\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t187 [label=\"Data.GraphViz.Attributes\\nHtmlLabel\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t321 [label=\"Data.GraphViz.Attributes\\nRecordLabel\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t365 [label=\"Data.GraphViz.Attributes\\nStrLabel\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_LayerID {\n\t\tgraph [label=\"Data: LayerID\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t83 [label=\"Data.GraphViz.Attributes\\nAllLayers\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t209 [label=\"Data.GraphViz.Attributes\\nLRInt\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t210 [label=\"Data.GraphViz.Attributes\\nLRName\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_LayerList {\n\t\tgraph [label=\"Data: LayerList\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t206 [label=\"Data.GraphViz.Attributes\\nLL\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_LayerRange {\n\t\tgraph [label=\"Data: LayerRange\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t208 [label=\"Data.GraphViz.Attributes\\nLRID\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t211 [label=\"Data.GraphViz.Attributes\\nLRS\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_ModeType {\n\t\tgraph [label=\"Data: ModeType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t184 [label=\"Data.GraphViz.Attributes\\nHier\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t196 [label=\"Data.GraphViz.Attributes\\nIpSep\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t203 [label=\"Data.GraphViz.Attributes\\nKK\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t244 [label=\"Data.GraphViz.Attributes\\nMajor\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Model {\n\t\tgraph [label=\"Data: Model\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t107 [label=\"Data.GraphViz.Attributes\\nCircuit\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t346 [label=\"Data.GraphViz.Attributes\\nShortPath\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t368 [label=\"Data.GraphViz.Attributes\\nSubSet\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_NodeCluster {\n\t\tgraph [label=\"Data: NodeCluster\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1667 [label=\"Data.GraphViz.Types.Clustering\\nC\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1669 [label=\"Data.GraphViz.Types.Clustering\\nN\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t}\n\tsubgraph cluster_Data_NodeInfo {\n\t\tgraph [label=\"Data: NodeInfo\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1828 [label=\"Data.GraphViz.Types.State\\nNI\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1841 [label=\"Data.GraphViz.Types.State\\natts\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1844 [label=\"Data.GraphViz.Types.State\\ngAtts\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1853 [label=\"Data.GraphViz.Types.State\\nlocation\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1841 -> 1828 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1844 -> 1828 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1853 -> 1828 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_OutputMode {\n\t\tgraph [label=\"Data: OutputMode\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t103 [label=\"Data.GraphViz.Attributes\\nBreadthFirst\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t146 [label=\"Data.GraphViz.Attributes\\nEdgesFirst\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t266 [label=\"Data.GraphViz.Attributes\\nNodesFirst\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Overlap {\n\t\tgraph [label=\"Data: Overlap\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t115 [label=\"Data.GraphViz.Attributes\\nCompressOverlap\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t197 [label=\"Data.GraphViz.Attributes\\nIpsepOverlap\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t204 [label=\"Data.GraphViz.Attributes\\nKeepOverlaps\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t307 [label=\"Data.GraphViz.Attributes\\nPrismOverlap\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t326 [label=\"Data.GraphViz.Attributes\\nRemoveOverlaps\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t338 [label=\"Data.GraphViz.Attributes\\nScaleOverlaps\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t339 [label=\"Data.GraphViz.Attributes\\nScaleXYOverlaps\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t397 [label=\"Data.GraphViz.Attributes\\nVpscOverlap\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Pack {\n\t\tgraph [label=\"Data: Pack\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t135 [label=\"Data.GraphViz.Attributes\\nDoPack\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t136 [label=\"Data.GraphViz.Attributes\\nDontPack\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t286 [label=\"Data.GraphViz.Attributes\\nPackMargin\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_PackMode {\n\t\tgraph [label=\"Data: PackMode\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t283 [label=\"Data.GraphViz.Attributes\\nPackArray\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t284 [label=\"Data.GraphViz.Attributes\\nPackClust\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t285 [label=\"Data.GraphViz.Attributes\\nPackGraph\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t288 [label=\"Data.GraphViz.Attributes\\nPackNode\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_PageDir {\n\t\tgraph [label=\"Data: PageDir\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t95 [label=\"Data.GraphViz.Attributes\\nBl\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t102 [label=\"Data.GraphViz.Attributes\\nBr\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t231 [label=\"Data.GraphViz.Attributes\\nLb\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t238 [label=\"Data.GraphViz.Attributes\\nLt\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t318 [label=\"Data.GraphViz.Attributes\\nRb\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t332 [label=\"Data.GraphViz.Attributes\\nRt\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t378 [label=\"Data.GraphViz.Attributes\\nTl\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t380 [label=\"Data.GraphViz.Attributes\\nTr\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Point {\n\t\tgraph [label=\"Data: Point\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t299 [label=\"Data.GraphViz.Attributes\\nPoint\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t415 [label=\"Data.GraphViz.Attributes\\nforcePos\", style=\"filled,solid\", shape=component, fillcolor=gold];\n\t\t607 [label=\"Data.GraphViz.Attributes\\nxCoord\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t608 [label=\"Data.GraphViz.Attributes\\nyCoord\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t609 [label=\"Data.GraphViz.Attributes\\nzCoord\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t415 -> 299 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t607 -> 299 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t608 -> 299 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t609 -> 299 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_PortName {\n\t\tgraph [label=\"Data: PortName\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1350 [label=\"Data.GraphViz.Attributes.Internal\\nPN\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1363 [label=\"Data.GraphViz.Attributes.Internal\\nportName\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1363 -> 1350 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_PortPos {\n\t\tgraph [label=\"Data: PortPos\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1343 [label=\"Data.GraphViz.Attributes.Internal\\nCompassPoint\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1345 [label=\"Data.GraphViz.Attributes.Internal\\nLabelledPort\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t}\n\tsubgraph cluster_Data_Pos {\n\t\tgraph [label=\"Data: Pos\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t300 [label=\"Data.GraphViz.Attributes\\nPointPos\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t358 [label=\"Data.GraphViz.Attributes\\nSplinePos\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_QuadType {\n\t\tgraph [label=\"Data: QuadType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t151 [label=\"Data.GraphViz.Attributes\\nFastQT\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t260 [label=\"Data.GraphViz.Attributes\\nNoQT\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t268 [label=\"Data.GraphViz.Attributes\\nNormalQT\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_RankDir {\n\t\tgraph [label=\"Data: RankDir\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t169 [label=\"Data.GraphViz.Attributes\\nFromBottom\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t170 [label=\"Data.GraphViz.Attributes\\nFromLeft\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t171 [label=\"Data.GraphViz.Attributes\\nFromRight\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t172 [label=\"Data.GraphViz.Attributes\\nFromTop\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_RankType {\n\t\tgraph [label=\"Data: RankType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t247 [label=\"Data.GraphViz.Attributes\\nMaxRank\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t250 [label=\"Data.GraphViz.Attributes\\nMinRank\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t335 [label=\"Data.GraphViz.Attributes\\nSameRank\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t349 [label=\"Data.GraphViz.Attributes\\nSinkRank\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t355 [label=\"Data.GraphViz.Attributes\\nSourceRank\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Ratios {\n\t\tgraph [label=\"Data: Ratios\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t89 [label=\"Data.GraphViz.Attributes\\nAspectRatio\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t90 [label=\"Data.GraphViz.Attributes\\nAutoRatio\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t116 [label=\"Data.GraphViz.Attributes\\nCompressRatio\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t150 [label=\"Data.GraphViz.Attributes\\nExpandRatio\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t156 [label=\"Data.GraphViz.Attributes\\nFillRatio\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_RecordField {\n\t\tgraph [label=\"Data: RecordField\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t152 [label=\"Data.GraphViz.Attributes\\nFieldLabel\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t161 [label=\"Data.GraphViz.Attributes\\nFlipFields\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t225 [label=\"Data.GraphViz.Attributes\\nLabelledTarget\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t304 [label=\"Data.GraphViz.Attributes\\nPortName\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Rect {\n\t\tgraph [label=\"Data: Rect\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t322 [label=\"Data.GraphViz.Attributes\\nRect\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Root {\n\t\tgraph [label=\"Data: Root\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t198 [label=\"Data.GraphViz.Attributes\\nIsCentral\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t264 [label=\"Data.GraphViz.Attributes\\nNodeName\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t270 [label=\"Data.GraphViz.Attributes\\nNotCentral\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_STStyle {\n\t\tgraph [label=\"Data: STStyle\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t311 [label=\"Data.GraphViz.Attributes\\nRandomStyle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t325 [label=\"Data.GraphViz.Attributes\\nRegularStyle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t341 [label=\"Data.GraphViz.Attributes\\nSelfStyle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_SameAttr {\n\t\tgraph [label=\"Data: SameAttr\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1829 [label=\"Data.GraphViz.Types.State\\nSA\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1845 [label=\"Data.GraphViz.Types.State\\ngetAttr\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1845 -> 1829 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_ScaleType {\n\t\tgraph [label=\"Data: ScaleType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t153 [label=\"Data.GraphViz.Attributes\\nFillBoth\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t155 [label=\"Data.GraphViz.Attributes\\nFillHeight\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t157 [label=\"Data.GraphViz.Attributes\\nFillWidth\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t261 [label=\"Data.GraphViz.Attributes\\nNoScale\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t387 [label=\"Data.GraphViz.Attributes\\nUniformScale\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Shape {\n\t\tgraph [label=\"Data: Shape\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t100 [label=\"Data.GraphViz.Attributes\\nBox3D\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t101 [label=\"Data.GraphViz.Attributes\\nBoxShape\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t106 [label=\"Data.GraphViz.Attributes\\nCircle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t112 [label=\"Data.GraphViz.Attributes\\nComponent\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t129 [label=\"Data.GraphViz.Attributes\\nDiamondShape\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t139 [label=\"Data.GraphViz.Attributes\\nDoubleCircle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t140 [label=\"Data.GraphViz.Attributes\\nDoubleOctagon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t147 [label=\"Data.GraphViz.Attributes\\nEgg\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t148 [label=\"Data.GraphViz.Attributes\\nEllipse\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t162 [label=\"Data.GraphViz.Attributes\\nFolder\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t183 [label=\"Data.GraphViz.Attributes\\nHexagon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t186 [label=\"Data.GraphViz.Attributes\\nHouse\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t192 [label=\"Data.GraphViz.Attributes\\nInvHouse\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t193 [label=\"Data.GraphViz.Attributes\\nInvTrapezium\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t194 [label=\"Data.GraphViz.Attributes\\nInvTriangle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t240 [label=\"Data.GraphViz.Attributes\\nMCircle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t241 [label=\"Data.GraphViz.Attributes\\nMDiamond\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t242 [label=\"Data.GraphViz.Attributes\\nMRecord\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t243 [label=\"Data.GraphViz.Attributes\\nMSquare\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t271 [label=\"Data.GraphViz.Attributes\\nNote\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t274 [label=\"Data.GraphViz.Attributes\\nOctagon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t292 [label=\"Data.GraphViz.Attributes\\nParallelogram\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t295 [label=\"Data.GraphViz.Attributes\\nPentagon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t298 [label=\"Data.GraphViz.Attributes\\nPlainText\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t301 [label=\"Data.GraphViz.Attributes\\nPointShape\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t303 [label=\"Data.GraphViz.Attributes\\nPolygon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t320 [label=\"Data.GraphViz.Attributes\\nRecord\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t343 [label=\"Data.GraphViz.Attributes\\nSeptagon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t369 [label=\"Data.GraphViz.Attributes\\nTab\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t381 [label=\"Data.GraphViz.Attributes\\nTrapezium\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t382 [label=\"Data.GraphViz.Attributes\\nTriangle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t384 [label=\"Data.GraphViz.Attributes\\nTripleOctagon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_SmoothType {\n\t\tgraph [label=\"Data: SmoothType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t91 [label=\"Data.GraphViz.Attributes\\nAvgDist\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t174 [label=\"Data.GraphViz.Attributes\\nGraphDist\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t262 [label=\"Data.GraphViz.Attributes\\nNoSmooth\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t306 [label=\"Data.GraphViz.Attributes\\nPowerDist\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t310 [label=\"Data.GraphViz.Attributes\\nRNG\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t360 [label=\"Data.GraphViz.Attributes\\nSpring\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t383 [label=\"Data.GraphViz.Attributes\\nTriangleSmooth\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Spline {\n\t\tgraph [label=\"Data: Spline\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t356 [label=\"Data.GraphViz.Attributes\\nSpline\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_StartType {\n\t\tgraph [label=\"Data: StartType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t362 [label=\"Data.GraphViz.Attributes\\nStartSeed\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t363 [label=\"Data.GraphViz.Attributes\\nStartStyle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t364 [label=\"Data.GraphViz.Attributes\\nStartStyleSeed\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_StateValue {\n\t\tgraph [label=\"Data: StateValue\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1830 [label=\"Data.GraphViz.Types.State\\nSV\", style=\"filled,solid\", shape=box3d, fillcolor=cyan];\n\t\t1851 [label=\"Data.GraphViz.Types.State\\nglobalAttrs\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1852 [label=\"Data.GraphViz.Types.State\\nglobalPath\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1869 [label=\"Data.GraphViz.Types.State\\nuseGlobals\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1870 [label=\"Data.GraphViz.Types.State\\nvalue\", style=\"filled,solid\", shape=component, fillcolor=bisque];\n\t\t1851 -> 1830 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1852 -> 1830 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1869 -> 1830 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1870 -> 1830 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_StyleItem {\n\t\tgraph [label=\"Data: StyleItem\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t333 [label=\"Data.GraphViz.Attributes\\nSItem\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_StyleName {\n\t\tgraph [label=\"Data: StyleName\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t96 [label=\"Data.GraphViz.Attributes\\nBold\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t120 [label=\"Data.GraphViz.Attributes\\nDD\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t124 [label=\"Data.GraphViz.Attributes\\nDashed\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t127 [label=\"Data.GraphViz.Attributes\\nDiagonals\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t138 [label=\"Data.GraphViz.Attributes\\nDotted\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t158 [label=\"Data.GraphViz.Attributes\\nFilled\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t195 [label=\"Data.GraphViz.Attributes\\nInvisible\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t331 [label=\"Data.GraphViz.Attributes\\nRounded\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t353 [label=\"Data.GraphViz.Attributes\\nSolid\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_Test {\n\t\tgraph [label=\"Data: Test\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t1490 [label=\"Data.GraphViz.Testing\\nTest\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t\t1493 [label=\"Data.GraphViz.Testing\\ndesc\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t1495 [label=\"Data.GraphViz.Testing\\nlookupName\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t1496 [label=\"Data.GraphViz.Testing\\nname\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t1501 [label=\"Data.GraphViz.Testing\\ntest\", style=\"filled,solid\", shape=component, fillcolor=crimson];\n\t\t1493 -> 1490 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1495 -> 1490 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1496 -> 1490 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t1501 -> 1490 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_VType {\n\t\tgraph [label=\"Data: VType\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t33 [label=\"Data.GraphViz.AttributeGenerator\\nBl\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t\t34 [label=\"Data.GraphViz.AttributeGenerator\\nCust\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t\t35 [label=\"Data.GraphViz.AttributeGenerator\\nDbl\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t\t36 [label=\"Data.GraphViz.AttributeGenerator\\nEStrng\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t\t37 [label=\"Data.GraphViz.AttributeGenerator\\nInteg\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t\t38 [label=\"Data.GraphViz.AttributeGenerator\\nStrng\", style=\"filled,solid\", shape=box3d, fillcolor=crimson];\n\t}\n\tsubgraph cluster_Data_VerticalPlacement {\n\t\tgraph [label=\"Data: VerticalPlacement\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t389 [label=\"Data.GraphViz.Attributes\\nVBottom\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t390 [label=\"Data.GraphViz.Attributes\\nVCenter\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t392 [label=\"Data.GraphViz.Attributes\\nVTop\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\tsubgraph cluster_Data_ViewPort {\n\t\tgraph [label=\"Data: ViewPort\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t391 [label=\"Data.GraphViz.Attributes\\nVP\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t414 [label=\"Data.GraphViz.Attributes\\nfocus\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t416 [label=\"Data.GraphViz.Attributes\\nhVal\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t606 [label=\"Data.GraphViz.Attributes\\nwVal\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t610 [label=\"Data.GraphViz.Attributes\\nzVal\", style=\"filled,solid\", shape=component, fillcolor=goldenrod];\n\t\t414 -> 391 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t416 -> 391 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t606 -> 391 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t\t610 -> 391 [penwidth=1, color=magenta, arrowtail=odot, arrowhead=vee];\n\t}\n\tsubgraph cluster_Data_X11Color {\n\t\tgraph [label=\"Data: X11Color\",\n\t\t\tstyle=\"filled,rounded\",\n\t\t\tfillcolor=papayawhip];\n\t\t612 [label=\"Data.GraphViz.Attributes.Colors\\nAliceBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t613 [label=\"Data.GraphViz.Attributes.Colors\\nAntiqueWhite\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t614 [label=\"Data.GraphViz.Attributes.Colors\\nAntiqueWhite1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t615 [label=\"Data.GraphViz.Attributes.Colors\\nAntiqueWhite2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t616 [label=\"Data.GraphViz.Attributes.Colors\\nAntiqueWhite3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t617 [label=\"Data.GraphViz.Attributes.Colors\\nAntiqueWhite4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t618 [label=\"Data.GraphViz.Attributes.Colors\\nAquamarine\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t619 [label=\"Data.GraphViz.Attributes.Colors\\nAquamarine1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t620 [label=\"Data.GraphViz.Attributes.Colors\\nAquamarine2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t621 [label=\"Data.GraphViz.Attributes.Colors\\nAquamarine3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t622 [label=\"Data.GraphViz.Attributes.Colors\\nAquamarine4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t623 [label=\"Data.GraphViz.Attributes.Colors\\nAzure\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t624 [label=\"Data.GraphViz.Attributes.Colors\\nAzure1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t625 [label=\"Data.GraphViz.Attributes.Colors\\nAzure2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t626 [label=\"Data.GraphViz.Attributes.Colors\\nAzure3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t627 [label=\"Data.GraphViz.Attributes.Colors\\nAzure4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t628 [label=\"Data.GraphViz.Attributes.Colors\\nBeige\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t629 [label=\"Data.GraphViz.Attributes.Colors\\nBisque\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t630 [label=\"Data.GraphViz.Attributes.Colors\\nBisque1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t631 [label=\"Data.GraphViz.Attributes.Colors\\nBisque2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t632 [label=\"Data.GraphViz.Attributes.Colors\\nBisque3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t633 [label=\"Data.GraphViz.Attributes.Colors\\nBisque4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t634 [label=\"Data.GraphViz.Attributes.Colors\\nBlack\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t635 [label=\"Data.GraphViz.Attributes.Colors\\nBlanchedAlmond\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t636 [label=\"Data.GraphViz.Attributes.Colors\\nBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t637 [label=\"Data.GraphViz.Attributes.Colors\\nBlue1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t638 [label=\"Data.GraphViz.Attributes.Colors\\nBlue2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t639 [label=\"Data.GraphViz.Attributes.Colors\\nBlue3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t640 [label=\"Data.GraphViz.Attributes.Colors\\nBlue4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t641 [label=\"Data.GraphViz.Attributes.Colors\\nBlueViolet\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t646 [label=\"Data.GraphViz.Attributes.Colors\\nBrown\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t647 [label=\"Data.GraphViz.Attributes.Colors\\nBrown1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t648 [label=\"Data.GraphViz.Attributes.Colors\\nBrown2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t649 [label=\"Data.GraphViz.Attributes.Colors\\nBrown3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t650 [label=\"Data.GraphViz.Attributes.Colors\\nBrown4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t653 [label=\"Data.GraphViz.Attributes.Colors\\nBurlywood\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t654 [label=\"Data.GraphViz.Attributes.Colors\\nBurlywood1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t655 [label=\"Data.GraphViz.Attributes.Colors\\nBurlywood2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t656 [label=\"Data.GraphViz.Attributes.Colors\\nBurlywood3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t657 [label=\"Data.GraphViz.Attributes.Colors\\nBurlywood4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t658 [label=\"Data.GraphViz.Attributes.Colors\\nCadetBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t659 [label=\"Data.GraphViz.Attributes.Colors\\nCadetBlue1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t660 [label=\"Data.GraphViz.Attributes.Colors\\nCadetBlue2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t661 [label=\"Data.GraphViz.Attributes.Colors\\nCadetBlue3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t662 [label=\"Data.GraphViz.Attributes.Colors\\nCadetBlue4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t663 [label=\"Data.GraphViz.Attributes.Colors\\nChartreuse\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t664 [label=\"Data.GraphViz.Attributes.Colors\\nChartreuse1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t665 [label=\"Data.GraphViz.Attributes.Colors\\nChartreuse2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t666 [label=\"Data.GraphViz.Attributes.Colors\\nChartreuse3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t667 [label=\"Data.GraphViz.Attributes.Colors\\nChartreuse4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t668 [label=\"Data.GraphViz.Attributes.Colors\\nChocolate\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t669 [label=\"Data.GraphViz.Attributes.Colors\\nChocolate1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t670 [label=\"Data.GraphViz.Attributes.Colors\\nChocolate2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t671 [label=\"Data.GraphViz.Attributes.Colors\\nChocolate3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t672 [label=\"Data.GraphViz.Attributes.Colors\\nChocolate4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t673 [label=\"Data.GraphViz.Attributes.Colors\\nCoral\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t674 [label=\"Data.GraphViz.Attributes.Colors\\nCoral1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t675 [label=\"Data.GraphViz.Attributes.Colors\\nCoral2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t676 [label=\"Data.GraphViz.Attributes.Colors\\nCoral3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t677 [label=\"Data.GraphViz.Attributes.Colors\\nCoral4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t678 [label=\"Data.GraphViz.Attributes.Colors\\nCornFlowerBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t679 [label=\"Data.GraphViz.Attributes.Colors\\nCornSilk\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t680 [label=\"Data.GraphViz.Attributes.Colors\\nCornSilk1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t681 [label=\"Data.GraphViz.Attributes.Colors\\nCornSilk2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t682 [label=\"Data.GraphViz.Attributes.Colors\\nCornSilk3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t683 [label=\"Data.GraphViz.Attributes.Colors\\nCornSilk4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t684 [label=\"Data.GraphViz.Attributes.Colors\\nCrimson\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t685 [label=\"Data.GraphViz.Attributes.Colors\\nCyan\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t686 [label=\"Data.GraphViz.Attributes.Colors\\nCyan1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t687 [label=\"Data.GraphViz.Attributes.Colors\\nCyan2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t688 [label=\"Data.GraphViz.Attributes.Colors\\nCyan3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t689 [label=\"Data.GraphViz.Attributes.Colors\\nCyan4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t691 [label=\"Data.GraphViz.Attributes.Colors\\nDarkGoldenrod\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t692 [label=\"Data.GraphViz.Attributes.Colors\\nDarkGoldenrod1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t693 [label=\"Data.GraphViz.Attributes.Colors\\nDarkGoldenrod2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t694 [label=\"Data.GraphViz.Attributes.Colors\\nDarkGoldenrod3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t695 [label=\"Data.GraphViz.Attributes.Colors\\nDarkGoldenrod4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t696 [label=\"Data.GraphViz.Attributes.Colors\\nDarkGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t697 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOliveGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t698 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOliveGreen1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t699 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOliveGreen2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t700 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOliveGreen3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t701 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOliveGreen4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t702 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOrange\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t703 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOrange1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t704 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOrange2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t705 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOrange3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t706 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOrange4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t707 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOrchid\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t708 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOrchid1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t709 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOrchid2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t710 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOrchid3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t711 [label=\"Data.GraphViz.Attributes.Colors\\nDarkOrchid4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t712 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSalmon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t713 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSeaGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t714 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSeaGreen1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t715 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSeaGreen2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t716 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSeaGreen3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t717 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSeaGreen4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t718 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSlateBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t719 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSlateGray\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t720 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSlateGray1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t721 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSlateGray2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t722 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSlateGray3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t723 [label=\"Data.GraphViz.Attributes.Colors\\nDarkSlateGray4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t724 [label=\"Data.GraphViz.Attributes.Colors\\nDarkTurquoise\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t725 [label=\"Data.GraphViz.Attributes.Colors\\nDarkViolet\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t726 [label=\"Data.GraphViz.Attributes.Colors\\nDarkkhaki\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t727 [label=\"Data.GraphViz.Attributes.Colors\\nDeepPink\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t728 [label=\"Data.GraphViz.Attributes.Colors\\nDeepPink1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t729 [label=\"Data.GraphViz.Attributes.Colors\\nDeepPink2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t730 [label=\"Data.GraphViz.Attributes.Colors\\nDeepPink3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t731 [label=\"Data.GraphViz.Attributes.Colors\\nDeepPink4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t732 [label=\"Data.GraphViz.Attributes.Colors\\nDeepSkyBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t733 [label=\"Data.GraphViz.Attributes.Colors\\nDeepSkyBlue1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t734 [label=\"Data.GraphViz.Attributes.Colors\\nDeepSkyBlue2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t735 [label=\"Data.GraphViz.Attributes.Colors\\nDeepSkyBlue3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t736 [label=\"Data.GraphViz.Attributes.Colors\\nDeepSkyBlue4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t737 [label=\"Data.GraphViz.Attributes.Colors\\nDimGray\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t738 [label=\"Data.GraphViz.Attributes.Colors\\nDodgerBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t739 [label=\"Data.GraphViz.Attributes.Colors\\nDodgerBlue1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t740 [label=\"Data.GraphViz.Attributes.Colors\\nDodgerBlue2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t741 [label=\"Data.GraphViz.Attributes.Colors\\nDodgerBlue3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t742 [label=\"Data.GraphViz.Attributes.Colors\\nDodgerBlue4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t743 [label=\"Data.GraphViz.Attributes.Colors\\nFirebrick\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t744 [label=\"Data.GraphViz.Attributes.Colors\\nFirebrick1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t745 [label=\"Data.GraphViz.Attributes.Colors\\nFirebrick2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t746 [label=\"Data.GraphViz.Attributes.Colors\\nFirebrick3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t747 [label=\"Data.GraphViz.Attributes.Colors\\nFirebrick4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t748 [label=\"Data.GraphViz.Attributes.Colors\\nFloralWhite\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t749 [label=\"Data.GraphViz.Attributes.Colors\\nForestGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t750 [label=\"Data.GraphViz.Attributes.Colors\\nGainsboro\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t751 [label=\"Data.GraphViz.Attributes.Colors\\nGhostWhite\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t753 [label=\"Data.GraphViz.Attributes.Colors\\nGold\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t754 [label=\"Data.GraphViz.Attributes.Colors\\nGold1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t755 [label=\"Data.GraphViz.Attributes.Colors\\nGold2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t756 [label=\"Data.GraphViz.Attributes.Colors\\nGold3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t757 [label=\"Data.GraphViz.Attributes.Colors\\nGold4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t758 [label=\"Data.GraphViz.Attributes.Colors\\nGoldenrod\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t759 [label=\"Data.GraphViz.Attributes.Colors\\nGoldenrod1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t760 [label=\"Data.GraphViz.Attributes.Colors\\nGoldenrod2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t761 [label=\"Data.GraphViz.Attributes.Colors\\nGoldenrod3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t762 [label=\"Data.GraphViz.Attributes.Colors\\nGoldenrod4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t763 [label=\"Data.GraphViz.Attributes.Colors\\nGray\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t764 [label=\"Data.GraphViz.Attributes.Colors\\nGray0\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t765 [label=\"Data.GraphViz.Attributes.Colors\\nGray1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t766 [label=\"Data.GraphViz.Attributes.Colors\\nGray10\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t767 [label=\"Data.GraphViz.Attributes.Colors\\nGray100\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t768 [label=\"Data.GraphViz.Attributes.Colors\\nGray11\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t769 [label=\"Data.GraphViz.Attributes.Colors\\nGray12\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t770 [label=\"Data.GraphViz.Attributes.Colors\\nGray13\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t771 [label=\"Data.GraphViz.Attributes.Colors\\nGray14\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t772 [label=\"Data.GraphViz.Attributes.Colors\\nGray15\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t773 [label=\"Data.GraphViz.Attributes.Colors\\nGray16\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t774 [label=\"Data.GraphViz.Attributes.Colors\\nGray17\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t775 [label=\"Data.GraphViz.Attributes.Colors\\nGray18\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t776 [label=\"Data.GraphViz.Attributes.Colors\\nGray19\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t777 [label=\"Data.GraphViz.Attributes.Colors\\nGray2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t778 [label=\"Data.GraphViz.Attributes.Colors\\nGray20\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t779 [label=\"Data.GraphViz.Attributes.Colors\\nGray21\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t780 [label=\"Data.GraphViz.Attributes.Colors\\nGray22\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t781 [label=\"Data.GraphViz.Attributes.Colors\\nGray23\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t782 [label=\"Data.GraphViz.Attributes.Colors\\nGray24\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t783 [label=\"Data.GraphViz.Attributes.Colors\\nGray25\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t784 [label=\"Data.GraphViz.Attributes.Colors\\nGray26\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t785 [label=\"Data.GraphViz.Attributes.Colors\\nGray27\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t786 [label=\"Data.GraphViz.Attributes.Colors\\nGray28\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t787 [label=\"Data.GraphViz.Attributes.Colors\\nGray29\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t788 [label=\"Data.GraphViz.Attributes.Colors\\nGray3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t789 [label=\"Data.GraphViz.Attributes.Colors\\nGray30\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t790 [label=\"Data.GraphViz.Attributes.Colors\\nGray31\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t791 [label=\"Data.GraphViz.Attributes.Colors\\nGray32\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t792 [label=\"Data.GraphViz.Attributes.Colors\\nGray33\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t793 [label=\"Data.GraphViz.Attributes.Colors\\nGray34\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t794 [label=\"Data.GraphViz.Attributes.Colors\\nGray35\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t795 [label=\"Data.GraphViz.Attributes.Colors\\nGray36\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t796 [label=\"Data.GraphViz.Attributes.Colors\\nGray37\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t797 [label=\"Data.GraphViz.Attributes.Colors\\nGray38\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t798 [label=\"Data.GraphViz.Attributes.Colors\\nGray39\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t799 [label=\"Data.GraphViz.Attributes.Colors\\nGray4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t800 [label=\"Data.GraphViz.Attributes.Colors\\nGray40\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t801 [label=\"Data.GraphViz.Attributes.Colors\\nGray41\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t802 [label=\"Data.GraphViz.Attributes.Colors\\nGray42\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t803 [label=\"Data.GraphViz.Attributes.Colors\\nGray43\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t804 [label=\"Data.GraphViz.Attributes.Colors\\nGray44\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t805 [label=\"Data.GraphViz.Attributes.Colors\\nGray45\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t806 [label=\"Data.GraphViz.Attributes.Colors\\nGray46\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t807 [label=\"Data.GraphViz.Attributes.Colors\\nGray47\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t808 [label=\"Data.GraphViz.Attributes.Colors\\nGray48\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t809 [label=\"Data.GraphViz.Attributes.Colors\\nGray49\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t810 [label=\"Data.GraphViz.Attributes.Colors\\nGray5\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t811 [label=\"Data.GraphViz.Attributes.Colors\\nGray50\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t812 [label=\"Data.GraphViz.Attributes.Colors\\nGray51\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t813 [label=\"Data.GraphViz.Attributes.Colors\\nGray52\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t814 [label=\"Data.GraphViz.Attributes.Colors\\nGray53\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t815 [label=\"Data.GraphViz.Attributes.Colors\\nGray54\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t816 [label=\"Data.GraphViz.Attributes.Colors\\nGray55\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t817 [label=\"Data.GraphViz.Attributes.Colors\\nGray56\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t818 [label=\"Data.GraphViz.Attributes.Colors\\nGray57\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t819 [label=\"Data.GraphViz.Attributes.Colors\\nGray58\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t820 [label=\"Data.GraphViz.Attributes.Colors\\nGray59\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t821 [label=\"Data.GraphViz.Attributes.Colors\\nGray6\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t822 [label=\"Data.GraphViz.Attributes.Colors\\nGray60\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t823 [label=\"Data.GraphViz.Attributes.Colors\\nGray61\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t824 [label=\"Data.GraphViz.Attributes.Colors\\nGray62\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t825 [label=\"Data.GraphViz.Attributes.Colors\\nGray63\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t826 [label=\"Data.GraphViz.Attributes.Colors\\nGray64\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t827 [label=\"Data.GraphViz.Attributes.Colors\\nGray65\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t828 [label=\"Data.GraphViz.Attributes.Colors\\nGray66\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t829 [label=\"Data.GraphViz.Attributes.Colors\\nGray67\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t830 [label=\"Data.GraphViz.Attributes.Colors\\nGray68\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t831 [label=\"Data.GraphViz.Attributes.Colors\\nGray69\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t832 [label=\"Data.GraphViz.Attributes.Colors\\nGray7\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t833 [label=\"Data.GraphViz.Attributes.Colors\\nGray70\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t834 [label=\"Data.GraphViz.Attributes.Colors\\nGray71\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t835 [label=\"Data.GraphViz.Attributes.Colors\\nGray72\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t836 [label=\"Data.GraphViz.Attributes.Colors\\nGray73\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t837 [label=\"Data.GraphViz.Attributes.Colors\\nGray74\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t838 [label=\"Data.GraphViz.Attributes.Colors\\nGray75\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t839 [label=\"Data.GraphViz.Attributes.Colors\\nGray76\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t840 [label=\"Data.GraphViz.Attributes.Colors\\nGray77\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t841 [label=\"Data.GraphViz.Attributes.Colors\\nGray78\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t842 [label=\"Data.GraphViz.Attributes.Colors\\nGray79\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t843 [label=\"Data.GraphViz.Attributes.Colors\\nGray8\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t844 [label=\"Data.GraphViz.Attributes.Colors\\nGray80\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t845 [label=\"Data.GraphViz.Attributes.Colors\\nGray81\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t846 [label=\"Data.GraphViz.Attributes.Colors\\nGray82\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t847 [label=\"Data.GraphViz.Attributes.Colors\\nGray83\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t848 [label=\"Data.GraphViz.Attributes.Colors\\nGray84\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t849 [label=\"Data.GraphViz.Attributes.Colors\\nGray85\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t850 [label=\"Data.GraphViz.Attributes.Colors\\nGray86\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t851 [label=\"Data.GraphViz.Attributes.Colors\\nGray87\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t852 [label=\"Data.GraphViz.Attributes.Colors\\nGray88\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t853 [label=\"Data.GraphViz.Attributes.Colors\\nGray89\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t854 [label=\"Data.GraphViz.Attributes.Colors\\nGray9\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t855 [label=\"Data.GraphViz.Attributes.Colors\\nGray90\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t856 [label=\"Data.GraphViz.Attributes.Colors\\nGray91\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t857 [label=\"Data.GraphViz.Attributes.Colors\\nGray92\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t858 [label=\"Data.GraphViz.Attributes.Colors\\nGray93\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t859 [label=\"Data.GraphViz.Attributes.Colors\\nGray94\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t860 [label=\"Data.GraphViz.Attributes.Colors\\nGray95\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t861 [label=\"Data.GraphViz.Attributes.Colors\\nGray96\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t862 [label=\"Data.GraphViz.Attributes.Colors\\nGray97\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t863 [label=\"Data.GraphViz.Attributes.Colors\\nGray98\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t864 [label=\"Data.GraphViz.Attributes.Colors\\nGray99\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t865 [label=\"Data.GraphViz.Attributes.Colors\\nGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t866 [label=\"Data.GraphViz.Attributes.Colors\\nGreen1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t867 [label=\"Data.GraphViz.Attributes.Colors\\nGreen2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t868 [label=\"Data.GraphViz.Attributes.Colors\\nGreen3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t869 [label=\"Data.GraphViz.Attributes.Colors\\nGreen4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t870 [label=\"Data.GraphViz.Attributes.Colors\\nGreenYellow\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t874 [label=\"Data.GraphViz.Attributes.Colors\\nHoneyDew\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t875 [label=\"Data.GraphViz.Attributes.Colors\\nHoneyDew1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t876 [label=\"Data.GraphViz.Attributes.Colors\\nHoneyDew2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t877 [label=\"Data.GraphViz.Attributes.Colors\\nHoneyDew3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t878 [label=\"Data.GraphViz.Attributes.Colors\\nHoneyDew4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t879 [label=\"Data.GraphViz.Attributes.Colors\\nHotPink\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t880 [label=\"Data.GraphViz.Attributes.Colors\\nHotPink1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t881 [label=\"Data.GraphViz.Attributes.Colors\\nHotPink2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t882 [label=\"Data.GraphViz.Attributes.Colors\\nHotPink3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t883 [label=\"Data.GraphViz.Attributes.Colors\\nHotPink4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t884 [label=\"Data.GraphViz.Attributes.Colors\\nIndianRed\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t885 [label=\"Data.GraphViz.Attributes.Colors\\nIndianRed1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t886 [label=\"Data.GraphViz.Attributes.Colors\\nIndianRed2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t887 [label=\"Data.GraphViz.Attributes.Colors\\nIndianRed3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t888 [label=\"Data.GraphViz.Attributes.Colors\\nIndianRed4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t889 [label=\"Data.GraphViz.Attributes.Colors\\nIndigo\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t890 [label=\"Data.GraphViz.Attributes.Colors\\nIvory\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t891 [label=\"Data.GraphViz.Attributes.Colors\\nIvory1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t892 [label=\"Data.GraphViz.Attributes.Colors\\nIvory2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t893 [label=\"Data.GraphViz.Attributes.Colors\\nIvory3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t894 [label=\"Data.GraphViz.Attributes.Colors\\nIvory4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t895 [label=\"Data.GraphViz.Attributes.Colors\\nKhaki\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t896 [label=\"Data.GraphViz.Attributes.Colors\\nKhaki1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t897 [label=\"Data.GraphViz.Attributes.Colors\\nKhaki2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t898 [label=\"Data.GraphViz.Attributes.Colors\\nKhaki3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t899 [label=\"Data.GraphViz.Attributes.Colors\\nKhaki4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t900 [label=\"Data.GraphViz.Attributes.Colors\\nLavender\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t901 [label=\"Data.GraphViz.Attributes.Colors\\nLavenderBlush\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t902 [label=\"Data.GraphViz.Attributes.Colors\\nLavenderBlush1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t903 [label=\"Data.GraphViz.Attributes.Colors\\nLavenderBlush2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t904 [label=\"Data.GraphViz.Attributes.Colors\\nLavenderBlush3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t905 [label=\"Data.GraphViz.Attributes.Colors\\nLavenderBlush4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t906 [label=\"Data.GraphViz.Attributes.Colors\\nLawnGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t907 [label=\"Data.GraphViz.Attributes.Colors\\nLemonChiffon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t908 [label=\"Data.GraphViz.Attributes.Colors\\nLemonChiffon1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t909 [label=\"Data.GraphViz.Attributes.Colors\\nLemonChiffon2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t910 [label=\"Data.GraphViz.Attributes.Colors\\nLemonChiffon3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t911 [label=\"Data.GraphViz.Attributes.Colors\\nLemonChiffon4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t912 [label=\"Data.GraphViz.Attributes.Colors\\nLightBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t913 [label=\"Data.GraphViz.Attributes.Colors\\nLightBlue1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t914 [label=\"Data.GraphViz.Attributes.Colors\\nLightBlue2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t915 [label=\"Data.GraphViz.Attributes.Colors\\nLightBlue3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t916 [label=\"Data.GraphViz.Attributes.Colors\\nLightBlue4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t917 [label=\"Data.GraphViz.Attributes.Colors\\nLightCoral\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t918 [label=\"Data.GraphViz.Attributes.Colors\\nLightCyan\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t919 [label=\"Data.GraphViz.Attributes.Colors\\nLightCyan1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t920 [label=\"Data.GraphViz.Attributes.Colors\\nLightCyan2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t921 [label=\"Data.GraphViz.Attributes.Colors\\nLightCyan3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t922 [label=\"Data.GraphViz.Attributes.Colors\\nLightCyan4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t923 [label=\"Data.GraphViz.Attributes.Colors\\nLightGoldenrod\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t924 [label=\"Data.GraphViz.Attributes.Colors\\nLightGoldenrod1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t925 [label=\"Data.GraphViz.Attributes.Colors\\nLightGoldenrod2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t926 [label=\"Data.GraphViz.Attributes.Colors\\nLightGoldenrod3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t927 [label=\"Data.GraphViz.Attributes.Colors\\nLightGoldenrod4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t928 [label=\"Data.GraphViz.Attributes.Colors\\nLightGoldenrodYellow\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t929 [label=\"Data.GraphViz.Attributes.Colors\\nLightGray\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t930 [label=\"Data.GraphViz.Attributes.Colors\\nLightPink\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t931 [label=\"Data.GraphViz.Attributes.Colors\\nLightPink1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t932 [label=\"Data.GraphViz.Attributes.Colors\\nLightPink2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t933 [label=\"Data.GraphViz.Attributes.Colors\\nLightPink3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t934 [label=\"Data.GraphViz.Attributes.Colors\\nLightPink4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t935 [label=\"Data.GraphViz.Attributes.Colors\\nLightSalmon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t936 [label=\"Data.GraphViz.Attributes.Colors\\nLightSalmon1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t937 [label=\"Data.GraphViz.Attributes.Colors\\nLightSalmon2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t938 [label=\"Data.GraphViz.Attributes.Colors\\nLightSalmon3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t939 [label=\"Data.GraphViz.Attributes.Colors\\nLightSalmon4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t940 [label=\"Data.GraphViz.Attributes.Colors\\nLightSeaGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t941 [label=\"Data.GraphViz.Attributes.Colors\\nLightSkyBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t942 [label=\"Data.GraphViz.Attributes.Colors\\nLightSkyBlue1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t943 [label=\"Data.GraphViz.Attributes.Colors\\nLightSkyBlue2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t944 [label=\"Data.GraphViz.Attributes.Colors\\nLightSkyBlue3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t945 [label=\"Data.GraphViz.Attributes.Colors\\nLightSkyBlue4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t946 [label=\"Data.GraphViz.Attributes.Colors\\nLightSlateBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t947 [label=\"Data.GraphViz.Attributes.Colors\\nLightSlateGray\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t948 [label=\"Data.GraphViz.Attributes.Colors\\nLightSteelBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t949 [label=\"Data.GraphViz.Attributes.Colors\\nLightSteelBlue1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t950 [label=\"Data.GraphViz.Attributes.Colors\\nLightSteelBlue2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t951 [label=\"Data.GraphViz.Attributes.Colors\\nLightSteelBlue3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t952 [label=\"Data.GraphViz.Attributes.Colors\\nLightSteelBlue4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t953 [label=\"Data.GraphViz.Attributes.Colors\\nLightYellow\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t954 [label=\"Data.GraphViz.Attributes.Colors\\nLightYellow1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t955 [label=\"Data.GraphViz.Attributes.Colors\\nLightYellow2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t956 [label=\"Data.GraphViz.Attributes.Colors\\nLightYellow3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t957 [label=\"Data.GraphViz.Attributes.Colors\\nLightYellow4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t958 [label=\"Data.GraphViz.Attributes.Colors\\nLimeGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t959 [label=\"Data.GraphViz.Attributes.Colors\\nLinen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t960 [label=\"Data.GraphViz.Attributes.Colors\\nMagenta\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t961 [label=\"Data.GraphViz.Attributes.Colors\\nMagenta1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t962 [label=\"Data.GraphViz.Attributes.Colors\\nMagenta2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t963 [label=\"Data.GraphViz.Attributes.Colors\\nMagenta3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t964 [label=\"Data.GraphViz.Attributes.Colors\\nMagenta4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t965 [label=\"Data.GraphViz.Attributes.Colors\\nMaroon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t966 [label=\"Data.GraphViz.Attributes.Colors\\nMaroon1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t967 [label=\"Data.GraphViz.Attributes.Colors\\nMaroon2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t968 [label=\"Data.GraphViz.Attributes.Colors\\nMaroon3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t969 [label=\"Data.GraphViz.Attributes.Colors\\nMaroon4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t970 [label=\"Data.GraphViz.Attributes.Colors\\nMediumAquamarine\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t971 [label=\"Data.GraphViz.Attributes.Colors\\nMediumBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t972 [label=\"Data.GraphViz.Attributes.Colors\\nMediumOrchid\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t973 [label=\"Data.GraphViz.Attributes.Colors\\nMediumOrchid1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t974 [label=\"Data.GraphViz.Attributes.Colors\\nMediumOrchid2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t975 [label=\"Data.GraphViz.Attributes.Colors\\nMediumOrchid3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t976 [label=\"Data.GraphViz.Attributes.Colors\\nMediumOrchid4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t977 [label=\"Data.GraphViz.Attributes.Colors\\nMediumPurple\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t978 [label=\"Data.GraphViz.Attributes.Colors\\nMediumPurple1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t979 [label=\"Data.GraphViz.Attributes.Colors\\nMediumPurple2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t980 [label=\"Data.GraphViz.Attributes.Colors\\nMediumPurple3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t981 [label=\"Data.GraphViz.Attributes.Colors\\nMediumPurple4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t982 [label=\"Data.GraphViz.Attributes.Colors\\nMediumSeaGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t983 [label=\"Data.GraphViz.Attributes.Colors\\nMediumSlateBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t984 [label=\"Data.GraphViz.Attributes.Colors\\nMediumSpringGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t985 [label=\"Data.GraphViz.Attributes.Colors\\nMediumTurquoise\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t986 [label=\"Data.GraphViz.Attributes.Colors\\nMediumVioletRed\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t987 [label=\"Data.GraphViz.Attributes.Colors\\nMidnightBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t988 [label=\"Data.GraphViz.Attributes.Colors\\nMintCream\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t989 [label=\"Data.GraphViz.Attributes.Colors\\nMistyRose\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t990 [label=\"Data.GraphViz.Attributes.Colors\\nMistyRose1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t991 [label=\"Data.GraphViz.Attributes.Colors\\nMistyRose2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t992 [label=\"Data.GraphViz.Attributes.Colors\\nMistyRose3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t993 [label=\"Data.GraphViz.Attributes.Colors\\nMistyRose4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t994 [label=\"Data.GraphViz.Attributes.Colors\\nMoccasin\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t995 [label=\"Data.GraphViz.Attributes.Colors\\nNavajoWhite\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t996 [label=\"Data.GraphViz.Attributes.Colors\\nNavajoWhite1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t997 [label=\"Data.GraphViz.Attributes.Colors\\nNavajoWhite2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t998 [label=\"Data.GraphViz.Attributes.Colors\\nNavajoWhite3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t999 [label=\"Data.GraphViz.Attributes.Colors\\nNavajoWhite4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1000 [label=\"Data.GraphViz.Attributes.Colors\\nNavy\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1001 [label=\"Data.GraphViz.Attributes.Colors\\nNavyBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1002 [label=\"Data.GraphViz.Attributes.Colors\\nOldLace\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1003 [label=\"Data.GraphViz.Attributes.Colors\\nOliveDrab\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1004 [label=\"Data.GraphViz.Attributes.Colors\\nOliveDrab1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1005 [label=\"Data.GraphViz.Attributes.Colors\\nOliveDrab2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1006 [label=\"Data.GraphViz.Attributes.Colors\\nOliveDrab3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1007 [label=\"Data.GraphViz.Attributes.Colors\\nOliveDrab4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1008 [label=\"Data.GraphViz.Attributes.Colors\\nOrange\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1009 [label=\"Data.GraphViz.Attributes.Colors\\nOrange1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1010 [label=\"Data.GraphViz.Attributes.Colors\\nOrange2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1011 [label=\"Data.GraphViz.Attributes.Colors\\nOrange3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1012 [label=\"Data.GraphViz.Attributes.Colors\\nOrange4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1013 [label=\"Data.GraphViz.Attributes.Colors\\nOrangeRed\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1014 [label=\"Data.GraphViz.Attributes.Colors\\nOrangeRed1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1015 [label=\"Data.GraphViz.Attributes.Colors\\nOrangeRed2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1016 [label=\"Data.GraphViz.Attributes.Colors\\nOrangeRed3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1017 [label=\"Data.GraphViz.Attributes.Colors\\nOrangeRed4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1019 [label=\"Data.GraphViz.Attributes.Colors\\nOrchid\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1020 [label=\"Data.GraphViz.Attributes.Colors\\nOrchid1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1021 [label=\"Data.GraphViz.Attributes.Colors\\nOrchid2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1022 [label=\"Data.GraphViz.Attributes.Colors\\nOrchid3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1023 [label=\"Data.GraphViz.Attributes.Colors\\nOrchid4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1026 [label=\"Data.GraphViz.Attributes.Colors\\nPaleGoldenrod\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1027 [label=\"Data.GraphViz.Attributes.Colors\\nPaleGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1028 [label=\"Data.GraphViz.Attributes.Colors\\nPaleGreen1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1029 [label=\"Data.GraphViz.Attributes.Colors\\nPaleGreen2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1030 [label=\"Data.GraphViz.Attributes.Colors\\nPaleGreen3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1031 [label=\"Data.GraphViz.Attributes.Colors\\nPaleGreen4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1032 [label=\"Data.GraphViz.Attributes.Colors\\nPaleTurquoise\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1033 [label=\"Data.GraphViz.Attributes.Colors\\nPaleTurquoise1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1034 [label=\"Data.GraphViz.Attributes.Colors\\nPaleTurquoise2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1035 [label=\"Data.GraphViz.Attributes.Colors\\nPaleTurquoise3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1036 [label=\"Data.GraphViz.Attributes.Colors\\nPaleTurquoise4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1037 [label=\"Data.GraphViz.Attributes.Colors\\nPaleVioletRed\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1038 [label=\"Data.GraphViz.Attributes.Colors\\nPaleVioletRed1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1039 [label=\"Data.GraphViz.Attributes.Colors\\nPaleVioletRed2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1040 [label=\"Data.GraphViz.Attributes.Colors\\nPaleVioletRed3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1041 [label=\"Data.GraphViz.Attributes.Colors\\nPaleVioletRed4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1042 [label=\"Data.GraphViz.Attributes.Colors\\nPapayaWhip\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1045 [label=\"Data.GraphViz.Attributes.Colors\\nPeachPuff\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1046 [label=\"Data.GraphViz.Attributes.Colors\\nPeachPuff1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1047 [label=\"Data.GraphViz.Attributes.Colors\\nPeachPuff2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1048 [label=\"Data.GraphViz.Attributes.Colors\\nPeachPuff3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1049 [label=\"Data.GraphViz.Attributes.Colors\\nPeachPuff4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1050 [label=\"Data.GraphViz.Attributes.Colors\\nPeru\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1051 [label=\"Data.GraphViz.Attributes.Colors\\nPink\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1052 [label=\"Data.GraphViz.Attributes.Colors\\nPink1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1053 [label=\"Data.GraphViz.Attributes.Colors\\nPink2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1054 [label=\"Data.GraphViz.Attributes.Colors\\nPink3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1055 [label=\"Data.GraphViz.Attributes.Colors\\nPink4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1057 [label=\"Data.GraphViz.Attributes.Colors\\nPlum\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1058 [label=\"Data.GraphViz.Attributes.Colors\\nPlum1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1059 [label=\"Data.GraphViz.Attributes.Colors\\nPlum2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1060 [label=\"Data.GraphViz.Attributes.Colors\\nPlum3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1061 [label=\"Data.GraphViz.Attributes.Colors\\nPlum4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1062 [label=\"Data.GraphViz.Attributes.Colors\\nPowderBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1068 [label=\"Data.GraphViz.Attributes.Colors\\nPurple\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1069 [label=\"Data.GraphViz.Attributes.Colors\\nPurple1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1070 [label=\"Data.GraphViz.Attributes.Colors\\nPurple2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1071 [label=\"Data.GraphViz.Attributes.Colors\\nPurple3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1072 [label=\"Data.GraphViz.Attributes.Colors\\nPurple4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1081 [label=\"Data.GraphViz.Attributes.Colors\\nRed\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1082 [label=\"Data.GraphViz.Attributes.Colors\\nRed1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1083 [label=\"Data.GraphViz.Attributes.Colors\\nRed2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1084 [label=\"Data.GraphViz.Attributes.Colors\\nRed3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1085 [label=\"Data.GraphViz.Attributes.Colors\\nRed4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1087 [label=\"Data.GraphViz.Attributes.Colors\\nRosyBrown\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1088 [label=\"Data.GraphViz.Attributes.Colors\\nRosyBrown1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1089 [label=\"Data.GraphViz.Attributes.Colors\\nRosyBrown2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1090 [label=\"Data.GraphViz.Attributes.Colors\\nRosyBrown3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1091 [label=\"Data.GraphViz.Attributes.Colors\\nRosyBrown4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1092 [label=\"Data.GraphViz.Attributes.Colors\\nRoyalBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1093 [label=\"Data.GraphViz.Attributes.Colors\\nRoyalBlue1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1094 [label=\"Data.GraphViz.Attributes.Colors\\nRoyalBlue2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1095 [label=\"Data.GraphViz.Attributes.Colors\\nRoyalBlue3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1096 [label=\"Data.GraphViz.Attributes.Colors\\nRoyalBlue4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1097 [label=\"Data.GraphViz.Attributes.Colors\\nSaddleBrown\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1098 [label=\"Data.GraphViz.Attributes.Colors\\nSalmon\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1099 [label=\"Data.GraphViz.Attributes.Colors\\nSalmon1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1100 [label=\"Data.GraphViz.Attributes.Colors\\nSalmon2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1101 [label=\"Data.GraphViz.Attributes.Colors\\nSalmon3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1102 [label=\"Data.GraphViz.Attributes.Colors\\nSalmon4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1103 [label=\"Data.GraphViz.Attributes.Colors\\nSandyBrown\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1104 [label=\"Data.GraphViz.Attributes.Colors\\nSeaGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1105 [label=\"Data.GraphViz.Attributes.Colors\\nSeaGreen1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1106 [label=\"Data.GraphViz.Attributes.Colors\\nSeaGreen2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1107 [label=\"Data.GraphViz.Attributes.Colors\\nSeaGreen3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1108 [label=\"Data.GraphViz.Attributes.Colors\\nSeaGreen4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1109 [label=\"Data.GraphViz.Attributes.Colors\\nSeaShell\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1110 [label=\"Data.GraphViz.Attributes.Colors\\nSeaShell1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1111 [label=\"Data.GraphViz.Attributes.Colors\\nSeaShell2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1112 [label=\"Data.GraphViz.Attributes.Colors\\nSeaShell3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1113 [label=\"Data.GraphViz.Attributes.Colors\\nSeaShell4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1117 [label=\"Data.GraphViz.Attributes.Colors\\nSienna\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1118 [label=\"Data.GraphViz.Attributes.Colors\\nSienna1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1119 [label=\"Data.GraphViz.Attributes.Colors\\nSienna2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1120 [label=\"Data.GraphViz.Attributes.Colors\\nSienna3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1121 [label=\"Data.GraphViz.Attributes.Colors\\nSienna4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1122 [label=\"Data.GraphViz.Attributes.Colors\\nSkyBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1123 [label=\"Data.GraphViz.Attributes.Colors\\nSkyBlue1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1124 [label=\"Data.GraphViz.Attributes.Colors\\nSkyBlue2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1125 [label=\"Data.GraphViz.Attributes.Colors\\nSkyBlue3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1126 [label=\"Data.GraphViz.Attributes.Colors\\nSkyBlue4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1127 [label=\"Data.GraphViz.Attributes.Colors\\nSlateBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1128 [label=\"Data.GraphViz.Attributes.Colors\\nSlateBlue1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1129 [label=\"Data.GraphViz.Attributes.Colors\\nSlateBlue2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1130 [label=\"Data.GraphViz.Attributes.Colors\\nSlateBlue3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1131 [label=\"Data.GraphViz.Attributes.Colors\\nSlateBlue4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1132 [label=\"Data.GraphViz.Attributes.Colors\\nSlateGray\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1133 [label=\"Data.GraphViz.Attributes.Colors\\nSlateGray1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1134 [label=\"Data.GraphViz.Attributes.Colors\\nSlateGray2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1135 [label=\"Data.GraphViz.Attributes.Colors\\nSlateGray3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1136 [label=\"Data.GraphViz.Attributes.Colors\\nSlateGray4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1137 [label=\"Data.GraphViz.Attributes.Colors\\nSnow\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1138 [label=\"Data.GraphViz.Attributes.Colors\\nSnow1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1139 [label=\"Data.GraphViz.Attributes.Colors\\nSnow2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1140 [label=\"Data.GraphViz.Attributes.Colors\\nSnow3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1141 [label=\"Data.GraphViz.Attributes.Colors\\nSnow4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1143 [label=\"Data.GraphViz.Attributes.Colors\\nSpringGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1144 [label=\"Data.GraphViz.Attributes.Colors\\nSpringGreen1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1145 [label=\"Data.GraphViz.Attributes.Colors\\nSpringGreen2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1146 [label=\"Data.GraphViz.Attributes.Colors\\nSpringGreen3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1147 [label=\"Data.GraphViz.Attributes.Colors\\nSpringGreen4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1148 [label=\"Data.GraphViz.Attributes.Colors\\nSteelBlue\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1149 [label=\"Data.GraphViz.Attributes.Colors\\nSteelBlue1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1150 [label=\"Data.GraphViz.Attributes.Colors\\nSteelBlue2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1151 [label=\"Data.GraphViz.Attributes.Colors\\nSteelBlue3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1152 [label=\"Data.GraphViz.Attributes.Colors\\nSteelBlue4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1153 [label=\"Data.GraphViz.Attributes.Colors\\nTan\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1154 [label=\"Data.GraphViz.Attributes.Colors\\nTan1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1155 [label=\"Data.GraphViz.Attributes.Colors\\nTan2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1156 [label=\"Data.GraphViz.Attributes.Colors\\nTan3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1157 [label=\"Data.GraphViz.Attributes.Colors\\nTan4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1158 [label=\"Data.GraphViz.Attributes.Colors\\nThistle\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1159 [label=\"Data.GraphViz.Attributes.Colors\\nThistle1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1160 [label=\"Data.GraphViz.Attributes.Colors\\nThistle2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1161 [label=\"Data.GraphViz.Attributes.Colors\\nThistle3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1162 [label=\"Data.GraphViz.Attributes.Colors\\nThistle4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1163 [label=\"Data.GraphViz.Attributes.Colors\\nTomato\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1164 [label=\"Data.GraphViz.Attributes.Colors\\nTomato1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1165 [label=\"Data.GraphViz.Attributes.Colors\\nTomato2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1166 [label=\"Data.GraphViz.Attributes.Colors\\nTomato3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1167 [label=\"Data.GraphViz.Attributes.Colors\\nTomato4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1168 [label=\"Data.GraphViz.Attributes.Colors\\nTransparent\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1169 [label=\"Data.GraphViz.Attributes.Colors\\nTurquoise\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1170 [label=\"Data.GraphViz.Attributes.Colors\\nTurquoise1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1171 [label=\"Data.GraphViz.Attributes.Colors\\nTurquoise2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1172 [label=\"Data.GraphViz.Attributes.Colors\\nTurquoise3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1173 [label=\"Data.GraphViz.Attributes.Colors\\nTurquoise4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1174 [label=\"Data.GraphViz.Attributes.Colors\\nViolet\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1175 [label=\"Data.GraphViz.Attributes.Colors\\nVioletRed\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1176 [label=\"Data.GraphViz.Attributes.Colors\\nVioletRed1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1177 [label=\"Data.GraphViz.Attributes.Colors\\nVioletRed2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1178 [label=\"Data.GraphViz.Attributes.Colors\\nVioletRed3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1179 [label=\"Data.GraphViz.Attributes.Colors\\nVioletRed4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1180 [label=\"Data.GraphViz.Attributes.Colors\\nWheat\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1181 [label=\"Data.GraphViz.Attributes.Colors\\nWheat1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1182 [label=\"Data.GraphViz.Attributes.Colors\\nWheat2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1183 [label=\"Data.GraphViz.Attributes.Colors\\nWheat3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1184 [label=\"Data.GraphViz.Attributes.Colors\\nWheat4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1185 [label=\"Data.GraphViz.Attributes.Colors\\nWhite\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1186 [label=\"Data.GraphViz.Attributes.Colors\\nWhiteSmoke\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1189 [label=\"Data.GraphViz.Attributes.Colors\\nYellow\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1190 [label=\"Data.GraphViz.Attributes.Colors\\nYellow1\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1191 [label=\"Data.GraphViz.Attributes.Colors\\nYellow2\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1192 [label=\"Data.GraphViz.Attributes.Colors\\nYellow3\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1193 [label=\"Data.GraphViz.Attributes.Colors\\nYellow4\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t\t1194 [label=\"Data.GraphViz.Attributes.Colors\\nYellowGreen\", style=\"filled,solid\", shape=box3d, fillcolor=goldenrod];\n\t}\n\t3 [label=\"Data.GraphViz\\naddEdgeIDs\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t4 [label=\"Data.GraphViz\\naugmentGraph\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t5 [label=\"Data.GraphViz\\nblankParams\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t6 [label=\"Data.GraphViz\\ncanonicalise\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t9 [label=\"Data.GraphViz\\ndefaultParams\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t10 [label=\"Data.GraphViz\\ndotAttributes\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t11 [label=\"Data.GraphViz\\ndotToGraph\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t12 [label=\"Data.GraphViz\\ndotizeGraph\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t18 [label=\"Data.GraphViz\\nfromDotResult\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t20 [label=\"Data.GraphViz\\ngraphToDot\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t21 [label=\"Data.GraphViz\\ngraphToGraph\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t23 [label=\"Data.GraphViz\\nisUndirected\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t24 [label=\"Data.GraphViz\\nnonClusteredParams\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t25 [label=\"Data.GraphViz\\nprettyPrint\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t26 [label=\"Data.GraphViz\\nprettyPrint'\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t27 [label=\"Data.GraphViz\\npreview\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t28 [label=\"Data.GraphViz\\nsetDirectedness\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t29 [label=\"Data.GraphViz\\nsetEdgeComment\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t30 [label=\"Data.GraphViz\\nstripID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t39 [label=\"Data.GraphViz.AttributeGenerator\\narbitraryFor\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t40 [label=\"Data.GraphViz.AttributeGenerator\\narbitraryFor'\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t41 [label=\"Data.GraphViz.AttributeGenerator\\narbitraryInstance\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t42 [label=\"Data.GraphViz.AttributeGenerator\\nasRows\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t43 [label=\"Data.GraphViz.AttributeGenerator\\nattributes\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t44 [label=\"Data.GraphViz.AttributeGenerator\\nattrs\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t45 [label=\"Data.GraphViz.AttributeGenerator\\nattrs'\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t47 [label=\"Data.GraphViz.AttributeGenerator\\nbool\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t50 [label=\"Data.GraphViz.AttributeGenerator\\ncreateAlias\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t51 [label=\"Data.GraphViz.AttributeGenerator\\ncreateDefn\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t52 [label=\"Data.GraphViz.AttributeGenerator\\ndocLen\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t53 [label=\"Data.GraphViz.AttributeGenerator\\ndocList\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t54 [label=\"Data.GraphViz.AttributeGenerator\\ndollar\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t55 [label=\"Data.GraphViz.AttributeGenerator\\ndot\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t56 [label=\"Data.GraphViz.AttributeGenerator\\nfirstOthers\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t62 [label=\"Data.GraphViz.AttributeGenerator\\ngenArbitrary\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t63 [label=\"Data.GraphViz.AttributeGenerator\\ngenCode\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t64 [label=\"Data.GraphViz.AttributeGenerator\\nmain\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t65 [label=\"Data.GraphViz.AttributeGenerator\\nmakeAttr\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t68 [label=\"Data.GraphViz.AttributeGenerator\\nparseInstance\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t70 [label=\"Data.GraphViz.AttributeGenerator\\nsameAttributeFunc\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t71 [label=\"Data.GraphViz.AttributeGenerator\\nshowInstance\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t72 [label=\"Data.GraphViz.AttributeGenerator\\nshrinkFor\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t73 [label=\"Data.GraphViz.AttributeGenerator\\ntab\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t75 [label=\"Data.GraphViz.AttributeGenerator\\nunknownAttr\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t76 [label=\"Data.GraphViz.AttributeGenerator\\nusedByFunc\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t78 [label=\"Data.GraphViz.AttributeGenerator\\nvsep\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t79 [label=\"Data.GraphViz.AttributeGenerator\\nvtype\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t80 [label=\"Data.GraphViz.AttributeGenerator\\nvtypeCode\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t81 [label=\"Data.GraphViz.AttributeGenerator\\nwrap\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t404 [label=\"Data.GraphViz.Attributes\\nbox\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t405 [label=\"Data.GraphViz.Attributes\\ncheckDD\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t406 [label=\"Data.GraphViz.Attributes\\ncheckLayerName\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t407 [label=\"Data.GraphViz.Attributes\\ncreatePoint\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t408 [label=\"Data.GraphViz.Attributes\\ncrow\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t409 [label=\"Data.GraphViz.Attributes\\ndefLayerSep\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t410 [label=\"Data.GraphViz.Attributes\\ndiamond\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t411 [label=\"Data.GraphViz.Attributes\\ndotArrow\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t412 [label=\"Data.GraphViz.Attributes\\neDiamond\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t413 [label=\"Data.GraphViz.Attributes\\nemptyArr\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t417 [label=\"Data.GraphViz.Attributes\\nhalfOpen\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t418 [label=\"Data.GraphViz.Attributes\\ninv\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t419 [label=\"Data.GraphViz.Attributes\\ninvDot\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t420 [label=\"Data.GraphViz.Attributes\\ninvEmpty\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t421 [label=\"Data.GraphViz.Attributes\\ninvODot\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t428 [label=\"Data.GraphViz.Attributes\\nnoArrow\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t429 [label=\"Data.GraphViz.Attributes\\nnoMods\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t430 [label=\"Data.GraphViz.Attributes\\nnormal\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t431 [label=\"Data.GraphViz.Attributes\\nnotLayerSep\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t432 [label=\"Data.GraphViz.Attributes\\noBox\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t433 [label=\"Data.GraphViz.Attributes\\noDiamond\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t434 [label=\"Data.GraphViz.Attributes\\noDot\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t435 [label=\"Data.GraphViz.Attributes\\nopenArr\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t436 [label=\"Data.GraphViz.Attributes\\nopenMod\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t457 [label=\"Data.GraphViz.Attributes\\nparseArgs\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t458 [label=\"Data.GraphViz.Attributes\\nparseLayerName\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t459 [label=\"Data.GraphViz.Attributes\\nparseLayerName'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t460 [label=\"Data.GraphViz.Attributes\\nparseLayerSep\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t464 [label=\"Data.GraphViz.Attributes\\nparsePoint2D\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t465 [label=\"Data.GraphViz.Attributes\\nparseRecord\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t466 [label=\"Data.GraphViz.Attributes\\nparseStyleName\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t515 [label=\"Data.GraphViz.Attributes\\nprintPortName\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t516 [label=\"Data.GraphViz.Attributes\\nrecordEscChars\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t517 [label=\"Data.GraphViz.Attributes\\nsameAttribute\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t518 [label=\"Data.GraphViz.Attributes\\nspecialArrowParse\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t519 [label=\"Data.GraphViz.Attributes\\ntee\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t599 [label=\"Data.GraphViz.Attributes\\nunqtRecordString\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t600 [label=\"Data.GraphViz.Attributes\\nusedByClusters\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t601 [label=\"Data.GraphViz.Attributes\\nusedByEdges\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t602 [label=\"Data.GraphViz.Attributes\\nusedByGraphs\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t603 [label=\"Data.GraphViz.Attributes\\nusedByNodes\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t604 [label=\"Data.GraphViz.Attributes\\nusedBySubGraphs\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t605 [label=\"Data.GraphViz.Attributes\\nvee\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1201 [label=\"Data.GraphViz.Attributes.Colors\\nfromAColour\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1202 [label=\"Data.GraphViz.Attributes.Colors\\nfromColour\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1204 [label=\"Data.GraphViz.Attributes.Colors\\nhexColor\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1207 [label=\"Data.GraphViz.Attributes.Colors\\nmaxWord\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1217 [label=\"Data.GraphViz.Attributes.Colors\\ntoColour\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1219 [label=\"Data.GraphViz.Attributes.Colors\\ntoOpacity\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1226 [label=\"Data.GraphViz.Attributes.Colors\\nword8Doc\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1227 [label=\"Data.GraphViz.Attributes.Colors\\nx11Colour\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1272 [label=\"Data.GraphViz.Attributes.HTML\\nescapeAttribute\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1273 [label=\"Data.GraphViz.Attributes.HTML\\nescapeHtml\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1274 [label=\"Data.GraphViz.Attributes.HTML\\nescapeValue\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1275 [label=\"Data.GraphViz.Attributes.HTML\\nhtmlEscapes\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1276 [label=\"Data.GraphViz.Attributes.HTML\\nhtmlUnescapes\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1291 [label=\"Data.GraphViz.Attributes.HTML\\nparseBoolHtml\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1292 [label=\"Data.GraphViz.Attributes.HTML\\nparseHtmlEmptyTag\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1293 [label=\"Data.GraphViz.Attributes.HTML\\nparseHtmlField\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1294 [label=\"Data.GraphViz.Attributes.HTML\\nparseHtmlField'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1295 [label=\"Data.GraphViz.Attributes.HTML\\nparseHtmlFontTag\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1296 [label=\"Data.GraphViz.Attributes.HTML\\nparseHtmlTag\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1315 [label=\"Data.GraphViz.Attributes.HTML\\nprintBoolHtml\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1316 [label=\"Data.GraphViz.Attributes.HTML\\nprintCell\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1317 [label=\"Data.GraphViz.Attributes.HTML\\nprintHtmlEmptyTag\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1318 [label=\"Data.GraphViz.Attributes.HTML\\nprintHtmlField\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1319 [label=\"Data.GraphViz.Attributes.HTML\\nprintHtmlField'\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1320 [label=\"Data.GraphViz.Attributes.HTML\\nprintHtmlFontTag\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1321 [label=\"Data.GraphViz.Attributes.HTML\\nprintHtmlTag\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1325 [label=\"Data.GraphViz.Attributes.HTML\\nunescapeAttribute\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1326 [label=\"Data.GraphViz.Attributes.HTML\\nunescapeHtml\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1327 [label=\"Data.GraphViz.Attributes.HTML\\nunescapeValue\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1355 [label=\"Data.GraphViz.Attributes.Internal\\ncheckPortName\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1356 [label=\"Data.GraphViz.Attributes.Internal\\ncompassLookup\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1359 [label=\"Data.GraphViz.Attributes.Internal\\nparseEdgeBasedPP\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1369 [label=\"Data.GraphViz.Attributes.Internal\\nunqtPortName\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1370 [label=\"Data.GraphViz.Parsing\\nallWhitespace\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1371 [label=\"Data.GraphViz.Parsing\\nallWhitespace'\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1372 [label=\"Data.GraphViz.Parsing\\nbracket\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1373 [label=\"Data.GraphViz.Parsing\\ncharacter\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1374 [label=\"Data.GraphViz.Parsing\\ncommaSep\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1375 [label=\"Data.GraphViz.Parsing\\ncommaSep'\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1376 [label=\"Data.GraphViz.Parsing\\ncommaSepUnqt\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1377 [label=\"Data.GraphViz.Parsing\\nconsumeLine\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1378 [label=\"Data.GraphViz.Parsing\\ndiscard\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1379 [label=\"Data.GraphViz.Parsing\\nnewline\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1380 [label=\"Data.GraphViz.Parsing\\nnewline'\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1381 [label=\"Data.GraphViz.Parsing\\nnoneOf\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1382 [label=\"Data.GraphViz.Parsing\\nnumString\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1383 [label=\"Data.GraphViz.Parsing\\nonlyBool\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1384 [label=\"Data.GraphViz.Parsing\\noptionalQuoted\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1385 [label=\"Data.GraphViz.Parsing\\noptionalQuotedString\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1386 [label=\"Data.GraphViz.Parsing\\norQuote\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1391 [label=\"Data.GraphViz.Parsing\\nparseAndSpace\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1392 [label=\"Data.GraphViz.Parsing\\nparseAngled\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1393 [label=\"Data.GraphViz.Parsing\\nparseBraced\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1394 [label=\"Data.GraphViz.Parsing\\nparseComma\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1395 [label=\"Data.GraphViz.Parsing\\nparseEq\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1396 [label=\"Data.GraphViz.Parsing\\nparseEscaped\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1397 [label=\"Data.GraphViz.Parsing\\nparseField\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1398 [label=\"Data.GraphViz.Parsing\\nparseFieldBool\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1399 [label=\"Data.GraphViz.Parsing\\nparseFieldDef\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1400 [label=\"Data.GraphViz.Parsing\\nparseFields\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1401 [label=\"Data.GraphViz.Parsing\\nparseFieldsBool\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1402 [label=\"Data.GraphViz.Parsing\\nparseFieldsDef\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1403 [label=\"Data.GraphViz.Parsing\\nparseFloat\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1404 [label=\"Data.GraphViz.Parsing\\nparseFloat'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1405 [label=\"Data.GraphViz.Parsing\\nparseInt\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1406 [label=\"Data.GraphViz.Parsing\\nparseInt'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1407 [label=\"Data.GraphViz.Parsing\\nparseIt\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1408 [label=\"Data.GraphViz.Parsing\\nparseIt'\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1413 [label=\"Data.GraphViz.Parsing\\nparseQuote\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1414 [label=\"Data.GraphViz.Parsing\\nparseSigned\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1415 [label=\"Data.GraphViz.Parsing\\nparseStrictFloat\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1428 [label=\"Data.GraphViz.Parsing\\nquoteChar\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1429 [label=\"Data.GraphViz.Parsing\\nquotedParse\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1430 [label=\"Data.GraphViz.Parsing\\nquotedString\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1431 [label=\"Data.GraphViz.Parsing\\nquotelessString\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1432 [label=\"Data.GraphViz.Parsing\\nrunParser'\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1433 [label=\"Data.GraphViz.Parsing\\nstring\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1434 [label=\"Data.GraphViz.Parsing\\nstringBlock\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1435 [label=\"Data.GraphViz.Parsing\\nstringRep\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1436 [label=\"Data.GraphViz.Parsing\\nstringReps\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1437 [label=\"Data.GraphViz.Parsing\\nstrings\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1438 [label=\"Data.GraphViz.Parsing\\ntryParseList\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1439 [label=\"Data.GraphViz.Parsing\\ntryParseList'\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1440 [label=\"Data.GraphViz.Parsing\\nwhitespace\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1441 [label=\"Data.GraphViz.Parsing\\nwhitespace'\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1442 [label=\"Data.GraphViz.Parsing\\nwrapWhitespace\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1443 [label=\"Data.GraphViz.PreProcessing\\nparseConcatStrings\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1444 [label=\"Data.GraphViz.PreProcessing\\nparseHTML\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1445 [label=\"Data.GraphViz.PreProcessing\\nparseLineComment\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1446 [label=\"Data.GraphViz.PreProcessing\\nparseMultiLineComment\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1447 [label=\"Data.GraphViz.PreProcessing\\nparseOutUnwanted\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1448 [label=\"Data.GraphViz.PreProcessing\\nparsePreProcessor\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1449 [label=\"Data.GraphViz.PreProcessing\\nparseSplitLine\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1450 [label=\"Data.GraphViz.PreProcessing\\nparseUnwanted\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1451 [label=\"Data.GraphViz.PreProcessing\\npreProcess\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1452 [label=\"Data.GraphViz.Printing\\naddEscapes\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1453 [label=\"Data.GraphViz.Printing\\naddQuotes\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1454 [label=\"Data.GraphViz.Printing\\nangled\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1455 [label=\"Data.GraphViz.Printing\\ncommaDel\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1456 [label=\"Data.GraphViz.Printing\\nfslash\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1457 [label=\"Data.GraphViz.Printing\\nlang\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1462 [label=\"Data.GraphViz.Printing\\nneedsQuotes\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1463 [label=\"Data.GraphViz.Printing\\nprintEscaped\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1464 [label=\"Data.GraphViz.Printing\\nprintField\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1465 [label=\"Data.GraphViz.Printing\\nprintIt\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1466 [label=\"Data.GraphViz.Printing\\nqtChar\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1467 [label=\"Data.GraphViz.Printing\\nqtString\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1468 [label=\"Data.GraphViz.Printing\\nrang\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1469 [label=\"Data.GraphViz.Printing\\nrenderDot\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1483 [label=\"Data.GraphViz.Printing\\nunqtEscaped\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1488 [label=\"Data.GraphViz.Printing\\nunqtString\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1489 [label=\"Data.GraphViz.Printing\\nwrap\", style=\"filled,solid\", shape=box, fillcolor=goldenrod];\n\t1491 [label=\"Data.GraphViz.Testing\\nblankLn\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1492 [label=\"Data.GraphViz.Testing\\ndefaultTests\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1494 [label=\"Data.GraphViz.Testing\\ndie\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1497 [label=\"Data.GraphViz.Testing\\nrunChosenTests\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1498 [label=\"Data.GraphViz.Testing\\nrunTest\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1499 [label=\"Data.GraphViz.Testing\\nrunTests\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1500 [label=\"Data.GraphViz.Testing\\nspacerLn\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1502 [label=\"Data.GraphViz.Testing\\ntest_dotizeAugment\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1503 [label=\"Data.GraphViz.Testing\\ntest_dotizeAugmentUniq\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1504 [label=\"Data.GraphViz.Testing\\ntest_findAllEdges\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1505 [label=\"Data.GraphViz.Testing\\ntest_findAllEdgesG\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1506 [label=\"Data.GraphViz.Testing\\ntest_findAllNodes\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1507 [label=\"Data.GraphViz.Testing\\ntest_findAllNodesE\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1508 [label=\"Data.GraphViz.Testing\\ntest_findAllNodesEG\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1509 [label=\"Data.GraphViz.Testing\\ntest_findAllNodesG\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1510 [label=\"Data.GraphViz.Testing\\ntest_generalisedSameDot\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1511 [label=\"Data.GraphViz.Testing\\ntest_noGraphInfo\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1512 [label=\"Data.GraphViz.Testing\\ntest_noGraphInfoG\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1513 [label=\"Data.GraphViz.Testing\\ntest_parsePrettyID\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1514 [label=\"Data.GraphViz.Testing\\ntest_preProcessingID\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1515 [label=\"Data.GraphViz.Testing\\ntest_printParseGID\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1516 [label=\"Data.GraphViz.Testing\\ntest_printParseID\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1517 [label=\"Data.GraphViz.Testing\\ntest_printParseID_Attributes\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1518 [label=\"Data.GraphViz.Testing.Instances\\narbBounded\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1519 [label=\"Data.GraphViz.Testing.Instances\\narbDS\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1520 [label=\"Data.GraphViz.Testing.Instances\\narbField\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1521 [label=\"Data.GraphViz.Testing.Instances\\narbGDS\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1522 [label=\"Data.GraphViz.Testing.Instances\\narbHtml\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1523 [label=\"Data.GraphViz.Testing.Instances\\narbHtmlText\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1524 [label=\"Data.GraphViz.Testing.Instances\\narbHtmlTexts\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1525 [label=\"Data.GraphViz.Testing.Instances\\narbIDString\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1526 [label=\"Data.GraphViz.Testing.Instances\\narbLayerName\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1527 [label=\"Data.GraphViz.Testing.Instances\\narbList\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1528 [label=\"Data.GraphViz.Testing.Instances\\narbString\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1529 [label=\"Data.GraphViz.Testing.Instances\\narbStyleName\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1601 [label=\"Data.GraphViz.Testing.Instances\\nfromPositive\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1602 [label=\"Data.GraphViz.Testing.Instances\\ngenGDStmts\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1603 [label=\"Data.GraphViz.Testing.Instances\\nlrnameCheck\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1604 [label=\"Data.GraphViz.Testing.Instances\\nnonEmptyShrinks\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1605 [label=\"Data.GraphViz.Testing.Instances\\nnonEmptyShrinks'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1606 [label=\"Data.GraphViz.Testing.Instances\\nnotBool\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1607 [label=\"Data.GraphViz.Testing.Instances\\nnotCP\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1608 [label=\"Data.GraphViz.Testing.Instances\\nnotInt\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1609 [label=\"Data.GraphViz.Testing.Instances\\nnotNumStr\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1610 [label=\"Data.GraphViz.Testing.Instances\\nnotStr\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1611 [label=\"Data.GraphViz.Testing.Instances\\npoint2D\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1612 [label=\"Data.GraphViz.Testing.Instances\\nposArbitrary\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1613 [label=\"Data.GraphViz.Testing.Instances\\nreturnCheck\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1655 [label=\"Data.GraphViz.Testing.Instances\\nshrinkGDStmts\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1656 [label=\"Data.GraphViz.Testing.Instances\\nshrinkL\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1657 [label=\"Data.GraphViz.Testing.Instances\\nshrinkList\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1658 [label=\"Data.GraphViz.Testing.Instances\\nshrinkList'\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1659 [label=\"Data.GraphViz.Testing.Instances\\nshrinkM\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1660 [label=\"Data.GraphViz.Testing.Instances\\nshrinkString\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1661 [label=\"Data.GraphViz.Testing.Instances\\nsimplifyHtmlText\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1662 [label=\"Data.GraphViz.Testing.Instances\\nvalidSplineList\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1663 [label=\"Data.GraphViz.Testing.Instances\\nvalidString\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1664 [label=\"Data.GraphViz.Testing.Instances\\nvalidUnknown\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1671 [label=\"Data.GraphViz.Types.Clustering\\nclustOrder\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1672 [label=\"Data.GraphViz.Types.Clustering\\nclustToTree\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1673 [label=\"Data.GraphViz.Types.Clustering\\nclustersToNodes\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1674 [label=\"Data.GraphViz.Types.Clustering\\ncollapseNClusts\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1675 [label=\"Data.GraphViz.Types.Clustering\\ngetNodes\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1676 [label=\"Data.GraphViz.Types.Clustering\\nsameClust\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1677 [label=\"Data.GraphViz.Types.Clustering\\ntreeToDot\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1678 [label=\"Data.GraphViz.Types.Clustering\\ntreesToDot\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1690 [label=\"Data.GraphViz.Types.Common\\naddPortPos\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1692 [label=\"Data.GraphViz.Types.Common\\nclust\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1693 [label=\"Data.GraphViz.Types.Common\\nclust'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1694 [label=\"Data.GraphViz.Types.Common\\ndetermineType\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1695 [label=\"Data.GraphViz.Types.Common\\ndirEdge\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1696 [label=\"Data.GraphViz.Types.Common\\ndirEdge'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1697 [label=\"Data.GraphViz.Types.Common\\ndirGraph\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1698 [label=\"Data.GraphViz.Types.Common\\ndirGraph'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1705 [label=\"Data.GraphViz.Types.Common\\ninvalidEdge\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1706 [label=\"Data.GraphViz.Types.Common\\ninvalidGlobal\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1707 [label=\"Data.GraphViz.Types.Common\\ninvalidNode\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1711 [label=\"Data.GraphViz.Types.Common\\nmkEdge\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1712 [label=\"Data.GraphViz.Types.Common\\nmkEdges\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1719 [label=\"Data.GraphViz.Types.Common\\nparseAttrBased\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1720 [label=\"Data.GraphViz.Types.Common\\nparseAttrBasedList\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1721 [label=\"Data.GraphViz.Types.Common\\nparseBracesBased\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1722 [label=\"Data.GraphViz.Types.Common\\nparseEdgeID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1723 [label=\"Data.GraphViz.Types.Common\\nparseEdgeLine\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1724 [label=\"Data.GraphViz.Types.Common\\nparseEdgeNode\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1725 [label=\"Data.GraphViz.Types.Common\\nparseEdgeNodes\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1726 [label=\"Data.GraphViz.Types.Common\\nparseEdgeType\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1727 [label=\"Data.GraphViz.Types.Common\\nparseGlobAttrType\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1728 [label=\"Data.GraphViz.Types.Common\\nparseGraphID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1732 [label=\"Data.GraphViz.Types.Common\\nparseNodeID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1733 [label=\"Data.GraphViz.Types.Common\\nparseSGID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1734 [label=\"Data.GraphViz.Types.Common\\nparseStatements\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1735 [label=\"Data.GraphViz.Types.Common\\nparseStmtBased\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1736 [label=\"Data.GraphViz.Types.Common\\nparseSubGraphID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1744 [label=\"Data.GraphViz.Types.Common\\nprintAttrBased\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1745 [label=\"Data.GraphViz.Types.Common\\nprintAttrBasedList\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1746 [label=\"Data.GraphViz.Types.Common\\nprintBracesBased\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1747 [label=\"Data.GraphViz.Types.Common\\nprintEdgeID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1748 [label=\"Data.GraphViz.Types.Common\\nprintGlobAttrType\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1749 [label=\"Data.GraphViz.Types.Common\\nprintGraphID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1750 [label=\"Data.GraphViz.Types.Common\\nprintNodeID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1751 [label=\"Data.GraphViz.Types.Common\\nprintSGID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1752 [label=\"Data.GraphViz.Types.Common\\nprintStmtBased\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1753 [label=\"Data.GraphViz.Types.Common\\nprintStmtBasedList\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1754 [label=\"Data.GraphViz.Types.Common\\nprintSubGraphID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1755 [label=\"Data.GraphViz.Types.Common\\nsGraph\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1756 [label=\"Data.GraphViz.Types.Common\\nsGraph'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1757 [label=\"Data.GraphViz.Types.Common\\nstatementEnd\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1758 [label=\"Data.GraphViz.Types.Common\\nstrGraph\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1759 [label=\"Data.GraphViz.Types.Common\\nstrGraph'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1760 [label=\"Data.GraphViz.Types.Common\\nstringNum\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1762 [label=\"Data.GraphViz.Types.Common\\nundirEdge\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1763 [label=\"Data.GraphViz.Types.Common\\nundirEdge'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1764 [label=\"Data.GraphViz.Types.Common\\nundirGraph\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1765 [label=\"Data.GraphViz.Types.Common\\nundirGraph'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1790 [label=\"Data.GraphViz.Types.Generalised\\ngeneraliseDotGraph\", style=\"filled,solid\", shape=box, fillcolor=gold];\n\t1791 [label=\"Data.GraphViz.Types.Generalised\\ngeneraliseStatements\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1792 [label=\"Data.GraphViz.Types.Generalised\\ngeneraliseSubGraph\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1804 [label=\"Data.GraphViz.Types.Generalised\\nparseGStmts\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1812 [label=\"Data.GraphViz.Types.Generalised\\nprintGStmts\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1813 [label=\"Data.GraphViz.Types.Generalised\\nprintSubGraphID'\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1815 [label=\"Data.GraphViz.Types.Generalised\\nstatementEdges\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1816 [label=\"Data.GraphViz.Types.Generalised\\nstatementNodes\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1817 [label=\"Data.GraphViz.Types.Generalised\\nstatementStructure\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1818 [label=\"Data.GraphViz.Types.Generalised\\nstmtEdges\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1819 [label=\"Data.GraphViz.Types.Generalised\\nstmtNodes\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1820 [label=\"Data.GraphViz.Types.Generalised\\nstmtStructure\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1826 [label=\"Data.GraphViz.Types.Generalised\\nwithSubGraphID\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1831 [label=\"Data.GraphViz.Types.State\\naddCluster\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1832 [label=\"Data.GraphViz.Types.State\\naddEdge\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1833 [label=\"Data.GraphViz.Types.State\\naddEdgeGlobals\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1834 [label=\"Data.GraphViz.Types.State\\naddEdgeNodes\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1835 [label=\"Data.GraphViz.Types.State\\naddGlobals\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1836 [label=\"Data.GraphViz.Types.State\\naddGraphGlobals\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1837 [label=\"Data.GraphViz.Types.State\\naddNode\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1838 [label=\"Data.GraphViz.Types.State\\naddNodeGlobals\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1839 [label=\"Data.GraphViz.Types.State\\naddSubGraph\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1840 [label=\"Data.GraphViz.Types.State\\nappend\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1843 [label=\"Data.GraphViz.Types.State\\nempty\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1846 [label=\"Data.GraphViz.Types.State\\ngetDotEdges\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1847 [label=\"Data.GraphViz.Types.State\\ngetGlobals\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1848 [label=\"Data.GraphViz.Types.State\\ngetGraphInfo\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1849 [label=\"Data.GraphViz.Types.State\\ngetNodeLookup\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1850 [label=\"Data.GraphViz.Types.State\\ngetPath\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1854 [label=\"Data.GraphViz.Types.State\\nmergeCInfos\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1855 [label=\"Data.GraphViz.Types.State\\nmergeNInfos\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1856 [label=\"Data.GraphViz.Types.State\\nmergeNode\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1857 [label=\"Data.GraphViz.Types.State\\nmergePs\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1858 [label=\"Data.GraphViz.Types.State\\nmodifyGlobal\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1859 [label=\"Data.GraphViz.Types.State\\nmodifyPath\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1860 [label=\"Data.GraphViz.Types.State\\nmodifyValue\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1861 [label=\"Data.GraphViz.Types.State\\nrecursiveCall\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1862 [label=\"Data.GraphViz.Types.State\\nsingleton\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1863 [label=\"Data.GraphViz.Types.State\\nsnoc\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1864 [label=\"Data.GraphViz.Types.State\\ntoDotNodes\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1865 [label=\"Data.GraphViz.Types.State\\ntoList\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1866 [label=\"Data.GraphViz.Types.State\\ntoSAttr\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1867 [label=\"Data.GraphViz.Types.State\\nunSame\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1868 [label=\"Data.GraphViz.Types.State\\nunionWith\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1871 [label=\"Data.GraphViz.Util\\nbool\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1872 [label=\"Data.GraphViz.Util\\ndescapeQuotes\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1873 [label=\"Data.GraphViz.Util\\nescapeQuotes\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1874 [label=\"Data.GraphViz.Util\\nfrstIDString\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1875 [label=\"Data.GraphViz.Util\\ngroupSortBy\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1876 [label=\"Data.GraphViz.Util\\nisIDString\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1877 [label=\"Data.GraphViz.Util\\nisIntString\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1878 [label=\"Data.GraphViz.Util\\nisKeyword\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1879 [label=\"Data.GraphViz.Util\\nisNumString\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1880 [label=\"Data.GraphViz.Util\\nisSingle\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t1881 [label=\"Data.GraphViz.Util\\nkeywords\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1882 [label=\"Data.GraphViz.Util\\nrestIDString\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1883 [label=\"Data.GraphViz.Util\\nstringToInt\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1884 [label=\"Data.GraphViz.Util\\ntoDouble\", style=\"filled,solid\", shape=box, fillcolor=cyan];\n\t1885 [label=\"Data.GraphViz.Util\\nuniq\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1886 [label=\"Data.GraphViz.Util\\nuniqBy\", style=\"filled,solid\", shape=box, fillcolor=bisque];\n\t1887 [label=\"Main\\ndg\", style=\"filled,solid\", shape=box, fillcolor=crimson];\n\t3 -> 1 [penwidth=1, color=black];\n\t4 -> 1 [penwidth=1, color=black];\n\t4 -> 111 [penwidth=1, color=black];\n\t5 -> 2 [penwidth=1, color=black];\n\t5 -> 7 [penwidth=1, color=black];\n\t5 -> 8 [penwidth=1, color=black];\n\t5 -> 15 [penwidth=1, color=black];\n\t5 -> 16 [penwidth=1, color=black];\n\t5 -> 17 [penwidth=1, color=black];\n\t5 -> 19 [penwidth=1, color=black];\n\t5 -> 22 [penwidth=1, color=black];\n\t6 -> 25 [penwidth=1, color=black];\n\t9 -> 2 [penwidth=1, color=black];\n\t9 -> 7 [penwidth=1, color=black];\n\t9 -> 8 [penwidth=1, color=black];\n\t9 -> 15 [penwidth=1, color=black];\n\t9 -> 16 [penwidth=1, color=black];\n\t9 -> 17 [penwidth=1, color=black];\n\t9 -> 19 [penwidth=1, color=black];\n\t9 -> 22 [penwidth=1, color=black];\n\t9 -> 1669 [penwidth=1, color=black];\n\t10 -> 4 [penwidth=1, color=black];\n\t10 -> 18 [penwidth=1, color=black];\n\t11 -> 1885 [penwidth=1, color=black];\n\t11 -> 1886 [penwidth=1, color=black];\n\t12 -> 15 [penwidth=1, color=black];\n\t12 -> 16 [penwidth=1, color=black];\n\t12 -> 17 [penwidth=1, color=black];\n\t12 -> 21 [penwidth=1, color=black];\n\t20 -> 7 [penwidth=1, color=black];\n\t20 -> 8 [penwidth=1, color=black];\n\t20 -> 15 [penwidth=1, color=black];\n\t20 -> 16 [penwidth=1, color=black];\n\t20 -> 17 [penwidth=1, color=black];\n\t20 -> 19 [penwidth=1, color=black];\n\t20 -> 22 [penwidth=1, color=black];\n\t20 -> 1673 [penwidth=1, color=black];\n\t21 -> 3 [penwidth=1, color=black];\n\t21 -> 10 [penwidth=1, color=black];\n\t21 -> 16 [penwidth=\"1.6931471805599454\", color=black];\n\t21 -> 20 [penwidth=1, color=black];\n\t21 -> 22 [penwidth=1, color=black];\n\t21 -> 29 [penwidth=1, color=black];\n\t24 -> 9 [penwidth=1, color=chartreuse];\n\t25 -> 18 [penwidth=1, color=black];\n\t26 -> 25 [penwidth=1, color=black];\n\t27 -> 16 [penwidth=1, color=black];\n\t27 -> 17 [penwidth=1, color=black];\n\t27 -> 20 [penwidth=1, color=black];\n\t27 -> 24 [penwidth=1, color=black];\n\t27 -> 28 [penwidth=1, color=black];\n\t27 -> 537 [penwidth=\"1.6931471805599454\", color=black];\n\t28 -> 22 [penwidth=1, color=black];\n\t28 -> 23 [penwidth=1, color=black];\n\t29 -> 13 [penwidth=1, color=black];\n\t29 -> 30 [penwidth=1, color=black];\n\t29 -> 111 [penwidth=1, color=black];\n\t30 -> 14 [penwidth=1, color=chartreuse];\n\t39 -> 34 [penwidth=1, color=black];\n\t39 -> 36 [penwidth=1, color=black];\n\t39 -> 38 [penwidth=1, color=black];\n\t40 -> 39 [penwidth=1, color=black];\n\t40 -> 77 [penwidth=1, color=black];\n\t41 -> 38 [penwidth=\"2.09861228866811\", color=black];\n\t41 -> 39 [penwidth=1, color=black];\n\t41 -> 40 [penwidth=1, color=black];\n\t41 -> 42 [penwidth=\"2.09861228866811\", color=black];\n\t41 -> 46 [penwidth=\"2.09861228866811\", color=black];\n\t41 -> 48 [penwidth=\"2.09861228866811\", color=black];\n\t41 -> 54 [penwidth=1, color=black];\n\t41 -> 56 [penwidth=1, color=black];\n\t41 -> 69 [penwidth=1, color=black];\n\t41 -> 72 [penwidth=\"2.09861228866811\", color=black];\n\t41 -> 73 [penwidth=1, color=black];\n\t41 -> 74 [penwidth=1, color=black];\n\t41 -> 75 [penwidth=\"2.09861228866811\", color=black];\n\t41 -> 77 [penwidth=1, color=black];\n\t41 -> 78 [penwidth=\"1.6931471805599454\", color=black];\n\t42 -> 52 [penwidth=1, color=chartreuse];\n\t43 -> 33 [penwidth=\"3.833213344056216\", color=black];\n\t43 -> 34 [penwidth=\"5.007333185232471\", color=black];\n\t43 -> 35 [penwidth=\"4.367295829986475\", color=black];\n\t43 -> 36 [penwidth=\"3.70805020110221\", color=black];\n\t43 -> 37 [penwidth=\"3.3978952727983707\", color=black];\n\t43 -> 38 [penwidth=\"3.833213344056216\", color=black];\n\t43 -> 65 [penwidth=\"5.969813299576001\", color=black];\n\t44 -> 43 [penwidth=1, color=black];\n\t45 -> 32 [penwidth=1, color=black];\n\t45 -> 44 [penwidth=1, color=black];\n\t50 -> 74 [penwidth=1, color=black];\n\t51 -> 38 [penwidth=\"1.6931471805599454\", color=black];\n\t51 -> 42 [penwidth=1, color=black];\n\t51 -> 46 [penwidth=1, color=black];\n\t51 -> 48 [penwidth=1, color=black];\n\t51 -> 49 [penwidth=1, color=black];\n\t51 -> 56 [penwidth=1, color=black];\n\t51 -> 73 [penwidth=\"1.6931471805599454\", color=black];\n\t51 -> 74 [penwidth=1, color=black];\n\t51 -> 75 [penwidth=1, color=black];\n\t51 -> 79 [penwidth=\"1.6931471805599454\", color=black];\n\t51 -> 80 [penwidth=1, color=black];\n\t62 -> 41 [penwidth=1, color=chartreuse];\n\t63 -> 50 [penwidth=1, color=black];\n\t63 -> 51 [penwidth=1, color=black];\n\t63 -> 57 [penwidth=1, color=black];\n\t63 -> 58 [penwidth=1, color=black];\n\t63 -> 59 [penwidth=1, color=black];\n\t63 -> 60 [penwidth=1, color=black];\n\t63 -> 61 [penwidth=1, color=black];\n\t63 -> 68 [penwidth=1, color=black];\n\t63 -> 70 [penwidth=1, color=black];\n\t63 -> 71 [penwidth=1, color=black];\n\t63 -> 76 [penwidth=\"2.6094379124341005\", color=black];\n\t63 -> 78 [penwidth=1, color=black];\n\t64 -> 32 [penwidth=1, color=black];\n\t64 -> 43 [penwidth=1, color=black];\n\t64 -> 46 [penwidth=1, color=black];\n\t64 -> 62 [penwidth=1, color=black];\n\t64 -> 63 [penwidth=1, color=black];\n\t64 -> 74 [penwidth=1, color=black];\n\t65 -> 31 [penwidth=1, color=black];\n\t65 -> 33 [penwidth=1, color=black];\n\t65 -> 48 [penwidth=1, color=black];\n\t65 -> 49 [penwidth=1, color=black];\n\t65 -> 57 [penwidth=1, color=black];\n\t65 -> 58 [penwidth=1, color=black];\n\t65 -> 59 [penwidth=1, color=black];\n\t65 -> 60 [penwidth=1, color=black];\n\t65 -> 61 [penwidth=1, color=black];\n\t65 -> 66 [penwidth=1, color=black];\n\t65 -> 67 [penwidth=1, color=black];\n\t65 -> 69 [penwidth=1, color=black];\n\t65 -> 77 [penwidth=1, color=black];\n\t65 -> 81 [penwidth=1, color=black];\n\t68 -> 33 [penwidth=1, color=black];\n\t68 -> 42 [penwidth=1, color=black];\n\t68 -> 46 [penwidth=1, color=black];\n\t68 -> 48 [penwidth=\"2.09861228866811\", color=black];\n\t68 -> 53 [penwidth=1, color=black];\n\t68 -> 56 [penwidth=1, color=black];\n\t68 -> 67 [penwidth=\"1.6931471805599454\", color=black];\n\t68 -> 69 [penwidth=1, color=black];\n\t68 -> 73 [penwidth=1, color=black];\n\t68 -> 74 [penwidth=1, color=black];\n\t68 -> 75 [penwidth=1, color=black];\n\t68 -> 77 [penwidth=1, color=black];\n\t68 -> 78 [penwidth=1, color=black];\n\t70 -> 42 [penwidth=1, color=black];\n\t70 -> 46 [penwidth=1, color=black];\n\t70 -> 48 [penwidth=\"1.6931471805599454\", color=black];\n\t70 -> 74 [penwidth=1, color=black];\n\t70 -> 75 [penwidth=\"1.6931471805599454\", color=black];\n\t71 -> 42 [penwidth=1, color=black];\n\t71 -> 46 [penwidth=1, color=black];\n\t71 -> 48 [penwidth=1, color=black];\n\t71 -> 66 [penwidth=1, color=black];\n\t71 -> 73 [penwidth=1, color=black];\n\t71 -> 74 [penwidth=1, color=black];\n\t71 -> 75 [penwidth=1, color=black];\n\t71 -> 78 [penwidth=1, color=black];\n\t72 -> 34 [penwidth=1, color=black];\n\t72 -> 36 [penwidth=1, color=black];\n\t72 -> 38 [penwidth=1, color=black];\n\t76 -> 42 [penwidth=1, color=black];\n\t76 -> 46 [penwidth=1, color=black];\n\t76 -> 48 [penwidth=1, color=black];\n\t76 -> 55 [penwidth=1, color=black];\n\t76 -> 74 [penwidth=1, color=black];\n\t76 -> 75 [penwidth=1, color=black];\n\t79 -> 33 [penwidth=1, color=black];\n\t79 -> 34 [penwidth=1, color=black];\n\t79 -> 35 [penwidth=1, color=black];\n\t79 -> 36 [penwidth=1, color=black];\n\t79 -> 37 [penwidth=1, color=black];\n\t79 -> 38 [penwidth=1, color=black];\n\t80 -> 77 [penwidth=1, color=black];\n\t80 -> 79 [penwidth=1, color=black];\n\t404 -> 82 [penwidth=1, color=black];\n\t404 -> 99 [penwidth=1, color=black];\n\t404 -> 429 [penwidth=1, color=black];\n\t405 -> 96 [penwidth=1, color=black];\n\t405 -> 120 [penwidth=1, color=black];\n\t405 -> 124 [penwidth=1, color=black];\n\t405 -> 127 [penwidth=1, color=black];\n\t405 -> 138 [penwidth=1, color=black];\n\t405 -> 158 [penwidth=1, color=black];\n\t405 -> 195 [penwidth=1, color=black];\n\t405 -> 331 [penwidth=1, color=black];\n\t405 -> 353 [penwidth=1, color=black];\n\t406 -> 83 [penwidth=1, color=black];\n\t406 -> 209 [penwidth=1, color=black];\n\t406 -> 210 [penwidth=1, color=black];\n\t406 -> 1883 [penwidth=1, color=black];\n\t407 -> 299 [penwidth=1, color=black];\n\t408 -> 82 [penwidth=1, color=black];\n\t408 -> 119 [penwidth=1, color=black];\n\t408 -> 429 [penwidth=1, color=black];\n\t410 -> 82 [penwidth=1, color=black];\n\t410 -> 128 [penwidth=1, color=black];\n\t410 -> 429 [penwidth=1, color=black];\n\t411 -> 82 [penwidth=1, color=black];\n\t411 -> 137 [penwidth=1, color=black];\n\t411 -> 429 [penwidth=1, color=black];\n\t412 -> 433 [penwidth=1, color=chartreuse];\n\t413 -> 82 [penwidth=1, color=black];\n\t413 -> 267 [penwidth=1, color=black];\n\t413 -> 436 [penwidth=1, color=black];\n\t417 -> 82 [penwidth=1, color=black];\n\t417 -> 84 [penwidth=1, color=black];\n\t417 -> 159 [penwidth=1, color=black];\n\t417 -> 232 [penwidth=1, color=black];\n\t417 -> 393 [penwidth=1, color=black];\n\t418 -> 82 [penwidth=1, color=black];\n\t418 -> 191 [penwidth=1, color=black];\n\t418 -> 429 [penwidth=1, color=black];\n\t419 -> 82 [penwidth=1, color=black];\n\t419 -> 137 [penwidth=1, color=black];\n\t419 -> 191 [penwidth=1, color=black];\n\t419 -> 429 [penwidth=\"1.6931471805599454\", color=black];\n\t420 -> 82 [penwidth=1, color=black];\n\t420 -> 191 [penwidth=1, color=black];\n\t420 -> 267 [penwidth=1, color=black];\n\t420 -> 429 [penwidth=1, color=black];\n\t420 -> 436 [penwidth=1, color=black];\n\t421 -> 82 [penwidth=1, color=black];\n\t421 -> 137 [penwidth=1, color=black];\n\t421 -> 191 [penwidth=1, color=black];\n\t421 -> 429 [penwidth=1, color=black];\n\t421 -> 436 [penwidth=1, color=black];\n\t427 -> 333 [penwidth=1, color=black];\n\t428 -> 82 [penwidth=1, color=black];\n\t428 -> 254 [penwidth=1, color=black];\n\t428 -> 429 [penwidth=1, color=black];\n\t429 -> 84 [penwidth=1, color=black];\n\t429 -> 98 [penwidth=1, color=black];\n\t429 -> 159 [penwidth=1, color=black];\n\t430 -> 82 [penwidth=1, color=black];\n\t430 -> 267 [penwidth=1, color=black];\n\t430 -> 429 [penwidth=1, color=black];\n\t431 -> 409 [penwidth=1, color=black];\n\t432 -> 82 [penwidth=1, color=black];\n\t432 -> 99 [penwidth=1, color=black];\n\t432 -> 436 [penwidth=1, color=black];\n\t433 -> 82 [penwidth=1, color=black];\n\t433 -> 128 [penwidth=1, color=black];\n\t433 -> 436 [penwidth=1, color=black];\n\t434 -> 82 [penwidth=1, color=black];\n\t434 -> 84 [penwidth=1, color=black];\n\t434 -> 98 [penwidth=1, color=black];\n\t434 -> 137 [penwidth=1, color=black];\n\t434 -> 275 [penwidth=1, color=black];\n\t435 -> 605 [penwidth=1, color=chartreuse];\n\t436 -> 84 [penwidth=1, color=black];\n\t436 -> 98 [penwidth=1, color=black];\n\t436 -> 275 [penwidth=1, color=black];\n\t439 -> 316 [penwidth=1, color=black];\n\t439 -> 317 [penwidth=1, color=black];\n\t439 -> 1376 [penwidth=1, color=black];\n\t439 -> 1429 [penwidth=1, color=black];\n\t441 -> 122 [penwidth=1, color=black];\n\t441 -> 1429 [penwidth=1, color=black];\n\t442 -> 258 [penwidth=1, color=black];\n\t442 -> 1384 [penwidth=1, color=black];\n\t442 -> 1435 [penwidth=1, color=black];\n\t443 -> 263 [penwidth=1, color=black];\n\t443 -> 400 [penwidth=1, color=black];\n\t444 -> 187 [penwidth=1, color=black];\n\t444 -> 321 [penwidth=1, color=black];\n\t444 -> 365 [penwidth=1, color=black];\n\t444 -> 1392 [penwidth=1, color=black];\n\t445 -> 209 [penwidth=1, color=black];\n\t445 -> 406 [penwidth=1, color=black];\n\t445 -> 459 [penwidth=1, color=black];\n\t446 -> 206 [penwidth=1, color=black];\n\t446 -> 210 [penwidth=1, color=black];\n\t446 -> 1429 [penwidth=1, color=black];\n\t446 -> 1434 [penwidth=1, color=black];\n\t447 -> 208 [penwidth=1, color=black];\n\t447 -> 211 [penwidth=1, color=black];\n\t447 -> 460 [penwidth=1, color=black];\n\t447 -> 1429 [penwidth=1, color=black];\n\t448 -> 1429 [penwidth=1, color=black];\n\t449 -> 1429 [penwidth=1, color=black];\n\t450 -> 1429 [penwidth=1, color=black];\n\t451 -> 1429 [penwidth=1, color=black];\n\t452 -> 198 [penwidth=1, color=black];\n\t452 -> 264 [penwidth=1, color=black];\n\t452 -> 270 [penwidth=1, color=black];\n\t452 -> 1383 [penwidth=1, color=black];\n\t452 -> 1384 [penwidth=1, color=black];\n\t452 -> 1871 [penwidth=1, color=black];\n\t453 -> 1429 [penwidth=1, color=black];\n\t454 -> 333 [penwidth=\"1.6931471805599454\", color=black];\n\t454 -> 457 [penwidth=1, color=black];\n\t454 -> 1429 [penwidth=1, color=black];\n\t455 -> 405 [penwidth=1, color=black];\n\t455 -> 1429 [penwidth=1, color=black];\n\t455 -> 1431 [penwidth=1, color=black];\n\t456 -> 1429 [penwidth=1, color=black];\n\t457 -> 466 [penwidth=1, color=black];\n\t457 -> 1373 [penwidth=\"1.6931471805599454\", color=black];\n\t457 -> 1394 [penwidth=1, color=black];\n\t458 -> 409 [penwidth=1, color=black];\n\t458 -> 1396 [penwidth=1, color=black];\n\t459 -> 458 [penwidth=1, color=black];\n\t459 -> 1429 [penwidth=1, color=black];\n\t459 -> 1434 [penwidth=1, color=black];\n\t460 -> 409 [penwidth=1, color=black];\n\t460 -> 1373 [penwidth=1, color=black];\n\t462 -> 152 [penwidth=1, color=black];\n\t462 -> 516 [penwidth=1, color=black];\n\t462 -> 1429 [penwidth=1, color=black];\n\t463 -> 1429 [penwidth=1, color=black];\n\t464 -> 407 [penwidth=1, color=black];\n\t464 -> 1376 [penwidth=1, color=black];\n\t465 -> 516 [penwidth=1, color=black];\n\t465 -> 1396 [penwidth=1, color=black];\n\t466 -> 1381 [penwidth=1, color=black];\n\t466 -> 1386 [penwidth=1, color=black];\n\t466 -> 1396 [penwidth=1, color=black];\n\t466 -> 1428 [penwidth=1, color=black];\n\t466 -> 1435 [penwidth=1, color=black];\n\t467 -> 159 [penwidth=1, color=black];\n\t467 -> 275 [penwidth=1, color=black];\n\t467 -> 1373 [penwidth=1, color=black];\n\t467 -> 1871 [penwidth=1, color=black];\n\t468 -> 84 [penwidth=1, color=black];\n\t469 -> 99 [penwidth=1, color=black];\n\t469 -> 119 [penwidth=1, color=black];\n\t469 -> 128 [penwidth=1, color=black];\n\t469 -> 137 [penwidth=1, color=black];\n\t469 -> 191 [penwidth=1, color=black];\n\t469 -> 254 [penwidth=1, color=black];\n\t469 -> 267 [penwidth=1, color=black];\n\t469 -> 377 [penwidth=1, color=black];\n\t469 -> 393 [penwidth=1, color=black];\n\t469 -> 1435 [penwidth=\"3.1972245773362196\", color=black];\n\t470 -> 98 [penwidth=1, color=black];\n\t470 -> 232 [penwidth=1, color=black];\n\t470 -> 328 [penwidth=1, color=black];\n\t470 -> 1373 [penwidth=1, color=black];\n\t470 -> 1871 [penwidth=1, color=black];\n\t471 -> 82 [penwidth=1, color=black];\n\t471 -> 518 [penwidth=1, color=black];\n\t472 -> 316 [penwidth=1, color=black];\n\t472 -> 317 [penwidth=1, color=black];\n\t472 -> 1376 [penwidth=1, color=black];\n\t473 -> 85 [penwidth=1, color=black];\n\t473 -> 86 [penwidth=1, color=black];\n\t473 -> 87 [penwidth=1, color=black];\n\t473 -> 88 [penwidth=1, color=black];\n\t473 -> 93 [penwidth=1, color=black];\n\t473 -> 94 [penwidth=1, color=black];\n\t473 -> 104 [penwidth=1, color=black];\n\t473 -> 105 [penwidth=1, color=black];\n\t473 -> 108 [penwidth=1, color=black];\n\t473 -> 109 [penwidth=1, color=black];\n\t473 -> 110 [penwidth=1, color=black];\n\t473 -> 111 [penwidth=1, color=black];\n\t473 -> 113 [penwidth=1, color=black];\n\t473 -> 117 [penwidth=1, color=black];\n\t473 -> 118 [penwidth=1, color=black];\n\t473 -> 121 [penwidth=1, color=black];\n\t473 -> 123 [penwidth=1, color=black];\n\t473 -> 125 [penwidth=1, color=black];\n\t473 -> 126 [penwidth=1, color=black];\n\t473 -> 130 [penwidth=1, color=black];\n\t473 -> 131 [penwidth=1, color=black];\n\t473 -> 132 [penwidth=1, color=black];\n\t473 -> 133 [penwidth=1, color=black];\n\t473 -> 134 [penwidth=1, color=black];\n\t473 -> 135 [penwidth=1, color=black];\n\t473 -> 141 [penwidth=1, color=black];\n\t473 -> 142 [penwidth=1, color=black];\n\t473 -> 143 [penwidth=1, color=black];\n\t473 -> 144 [penwidth=1, color=black];\n\t473 -> 145 [penwidth=1, color=black];\n\t473 -> 149 [penwidth=1, color=black];\n\t473 -> 154 [penwidth=1, color=black];\n\t473 -> 160 [penwidth=1, color=black];\n\t473 -> 163 [penwidth=1, color=black];\n\t473 -> 164 [penwidth=1, color=black];\n\t473 -> 165 [penwidth=1, color=black];\n\t473 -> 166 [penwidth=1, color=black];\n\t473 -> 167 [penwidth=1, color=black];\n\t473 -> 175 [penwidth=1, color=black];\n\t473 -> 176 [penwidth=1, color=black];\n\t473 -> 177 [penwidth=1, color=black];\n\t473 -> 178 [penwidth=1, color=black];\n\t473 -> 179 [penwidth=1, color=black];\n\t473 -> 180 [penwidth=1, color=black];\n\t473 -> 181 [penwidth=1, color=black];\n\t473 -> 182 [penwidth=1, color=black];\n\t473 -> 188 [penwidth=1, color=black];\n\t473 -> 189 [penwidth=1, color=black];\n\t473 -> 190 [penwidth=1, color=black];\n\t473 -> 198 [penwidth=1, color=black];\n\t473 -> 202 [penwidth=1, color=black];\n\t473 -> 204 [penwidth=1, color=black];\n\t473 -> 205 [penwidth=1, color=black];\n\t473 -> 207 [penwidth=1, color=black];\n\t473 -> 212 [penwidth=1, color=black];\n\t473 -> 213 [penwidth=1, color=black];\n\t473 -> 214 [penwidth=1, color=black];\n\t473 -> 215 [penwidth=1, color=black];\n\t473 -> 216 [penwidth=1, color=black];\n\t473 -> 217 [penwidth=1, color=black];\n\t473 -> 218 [penwidth=1, color=black];\n\t473 -> 219 [penwidth=1, color=black];\n\t473 -> 220 [penwidth=1, color=black];\n\t473 -> 221 [penwidth=1, color=black];\n\t473 -> 222 [penwidth=1, color=black];\n\t473 -> 223 [penwidth=1, color=black];\n\t473 -> 224 [penwidth=1, color=black];\n\t473 -> 226 [penwidth=1, color=black];\n\t473 -> 227 [penwidth=1, color=black];\n\t473 -> 228 [penwidth=1, color=black];\n\t473 -> 229 [penwidth=1, color=black];\n\t473 -> 230 [penwidth=1, color=black];\n\t473 -> 233 [penwidth=1, color=black];\n\t473 -> 234 [penwidth=1, color=black];\n\t473 -> 235 [penwidth=1, color=black];\n\t473 -> 239 [penwidth=1, color=black];\n\t473 -> 245 [penwidth=1, color=black];\n\t473 -> 246 [penwidth=1, color=black];\n\t473 -> 248 [penwidth=1, color=black];\n\t473 -> 249 [penwidth=1, color=black];\n\t473 -> 251 [penwidth=1, color=black];\n\t473 -> 252 [penwidth=1, color=black];\n\t473 -> 253 [penwidth=1, color=black];\n\t473 -> 259 [penwidth=1, color=black];\n\t473 -> 265 [penwidth=1, color=black];\n\t473 -> 268 [penwidth=1, color=black];\n\t473 -> 269 [penwidth=1, color=black];\n\t473 -> 272 [penwidth=1, color=black];\n\t473 -> 273 [penwidth=1, color=black];\n\t473 -> 276 [penwidth=1, color=black];\n\t473 -> 277 [penwidth=1, color=black];\n\t473 -> 278 [penwidth=1, color=black];\n\t473 -> 279 [penwidth=1, color=black];\n\t473 -> 280 [penwidth=1, color=black];\n\t473 -> 282 [penwidth=1, color=black];\n\t473 -> 287 [penwidth=1, color=black];\n\t473 -> 289 [penwidth=1, color=black];\n\t473 -> 290 [penwidth=1, color=black];\n\t473 -> 291 [penwidth=1, color=black];\n\t473 -> 293 [penwidth=1, color=black];\n\t473 -> 294 [penwidth=1, color=black];\n\t473 -> 296 [penwidth=1, color=black];\n\t473 -> 297 [penwidth=1, color=black];\n\t473 -> 305 [penwidth=1, color=black];\n\t473 -> 308 [penwidth=1, color=black];\n\t473 -> 309 [penwidth=1, color=black];\n\t473 -> 312 [penwidth=1, color=black];\n\t473 -> 313 [penwidth=1, color=black];\n\t473 -> 314 [penwidth=1, color=black];\n\t473 -> 315 [penwidth=1, color=black];\n\t473 -> 319 [penwidth=1, color=black];\n\t473 -> 323 [penwidth=1, color=black];\n\t473 -> 324 [penwidth=1, color=black];\n\t473 -> 327 [penwidth=1, color=black];\n\t473 -> 329 [penwidth=1, color=black];\n\t473 -> 330 [penwidth=1, color=black];\n\t473 -> 334 [penwidth=1, color=black];\n\t473 -> 336 [penwidth=1, color=black];\n\t473 -> 337 [penwidth=1, color=black];\n\t473 -> 340 [penwidth=1, color=black];\n\t473 -> 342 [penwidth=1, color=black];\n\t473 -> 344 [penwidth=1, color=black];\n\t473 -> 345 [penwidth=1, color=black];\n\t473 -> 347 [penwidth=1, color=black];\n\t473 -> 348 [penwidth=1, color=black];\n\t473 -> 350 [penwidth=1, color=black];\n\t473 -> 351 [penwidth=1, color=black];\n\t473 -> 352 [penwidth=1, color=black];\n\t473 -> 354 [penwidth=1, color=black];\n\t473 -> 357 [penwidth=1, color=black];\n\t473 -> 359 [penwidth=1, color=black];\n\t473 -> 361 [penwidth=1, color=black];\n\t473 -> 366 [penwidth=1, color=black];\n\t473 -> 367 [penwidth=1, color=black];\n\t473 -> 370 [penwidth=1, color=black];\n\t473 -> 371 [penwidth=1, color=black];\n\t473 -> 372 [penwidth=1, color=black];\n\t473 -> 373 [penwidth=1, color=black];\n\t473 -> 374 [penwidth=1, color=black];\n\t473 -> 375 [penwidth=1, color=black];\n\t473 -> 376 [penwidth=1, color=black];\n\t473 -> 379 [penwidth=1, color=black];\n\t473 -> 385 [penwidth=1, color=black];\n\t473 -> 386 [penwidth=1, color=black];\n\t473 -> 387 [penwidth=1, color=black];\n\t473 -> 388 [penwidth=1, color=black];\n\t473 -> 394 [penwidth=1, color=black];\n\t473 -> 395 [penwidth=1, color=black];\n\t473 -> 396 [penwidth=1, color=black];\n\t473 -> 398 [penwidth=1, color=black];\n\t473 -> 399 [penwidth=1, color=black];\n\t473 -> 401 [penwidth=1, color=black];\n\t473 -> 1395 [penwidth=1, color=black];\n\t473 -> 1397 [penwidth=\"5.736198448394496\", color=black];\n\t473 -> 1398 [penwidth=\"3.833213344056216\", color=black];\n\t473 -> 1399 [penwidth=\"2.9459101490553135\", color=black];\n\t473 -> 1400 [penwidth=\"2.791759469228055\", color=black];\n\t473 -> 1434 [penwidth=1, color=black];\n\t474 -> 173 [penwidth=1, color=black];\n\t474 -> 237 [penwidth=1, color=black];\n\t474 -> 255 [penwidth=1, color=black];\n\t474 -> 1435 [penwidth=\"2.09861228866811\", color=black];\n\t475 -> 142 [penwidth=1, color=black];\n\t475 -> 185 [penwidth=1, color=black];\n\t475 -> 256 [penwidth=1, color=black];\n\t475 -> 1435 [penwidth=1, color=black];\n\t475 -> 1871 [penwidth=1, color=black];\n\t476 -> 122 [penwidth=1, color=black];\n\t476 -> 281 [penwidth=1, color=black];\n\t476 -> 464 [penwidth=1, color=black];\n\t477 -> 92 [penwidth=1, color=black];\n\t477 -> 97 [penwidth=1, color=black];\n\t477 -> 168 [penwidth=1, color=black];\n\t477 -> 257 [penwidth=1, color=black];\n\t477 -> 1435 [penwidth=\"2.386294361119891\", color=black];\n\t478 -> 114 [penwidth=1, color=black];\n\t478 -> 236 [penwidth=\"1.6931471805599454\", color=black];\n\t478 -> 302 [penwidth=1, color=black];\n\t478 -> 357 [penwidth=\"1.6931471805599454\", color=black];\n\t478 -> 1435 [penwidth=\"2.386294361119891\", color=black];\n\t478 -> 1871 [penwidth=1, color=black];\n\t479 -> 263 [penwidth=1, color=black];\n\t479 -> 400 [penwidth=1, color=black];\n\t480 -> 199 [penwidth=1, color=black];\n\t480 -> 200 [penwidth=1, color=black];\n\t480 -> 201 [penwidth=1, color=black];\n\t480 -> 1435 [penwidth=\"2.09861228866811\", color=black];\n\t481 -> 187 [penwidth=1, color=black];\n\t481 -> 321 [penwidth=1, color=black];\n\t481 -> 365 [penwidth=1, color=black];\n\t481 -> 1392 [penwidth=1, color=black];\n\t482 -> 406 [penwidth=1, color=black];\n\t482 -> 458 [penwidth=1, color=black];\n\t483 -> 206 [penwidth=1, color=black];\n\t483 -> 460 [penwidth=1, color=black];\n\t484 -> 208 [penwidth=1, color=black];\n\t484 -> 211 [penwidth=1, color=black];\n\t484 -> 460 [penwidth=1, color=black];\n\t485 -> 184 [penwidth=1, color=black];\n\t485 -> 196 [penwidth=1, color=black];\n\t485 -> 203 [penwidth=1, color=black];\n\t485 -> 244 [penwidth=1, color=black];\n\t485 -> 1435 [penwidth=\"2.386294361119891\", color=black];\n\t486 -> 107 [penwidth=1, color=black];\n\t486 -> 346 [penwidth=1, color=black];\n\t486 -> 368 [penwidth=1, color=black];\n\t486 -> 1435 [penwidth=\"2.09861228866811\", color=black];\n\t487 -> 103 [penwidth=1, color=black];\n\t487 -> 146 [penwidth=1, color=black];\n\t487 -> 266 [penwidth=1, color=black];\n\t487 -> 1435 [penwidth=\"2.09861228866811\", color=black];\n\t488 -> 115 [penwidth=1, color=black];\n\t488 -> 197 [penwidth=1, color=black];\n\t488 -> 204 [penwidth=1, color=black];\n\t488 -> 307 [penwidth=1, color=black];\n\t488 -> 326 [penwidth=1, color=black];\n\t488 -> 338 [penwidth=1, color=black];\n\t488 -> 339 [penwidth=1, color=black];\n\t488 -> 397 [penwidth=1, color=black];\n\t488 -> 1433 [penwidth=1, color=black];\n\t488 -> 1435 [penwidth=\"2.9459101490553135\", color=black];\n\t489 -> 135 [penwidth=1, color=black];\n\t489 -> 136 [penwidth=1, color=black];\n\t489 -> 286 [penwidth=1, color=black];\n\t489 -> 1383 [penwidth=1, color=black];\n\t489 -> 1871 [penwidth=1, color=black];\n\t490 -> 283 [penwidth=1, color=black];\n\t490 -> 284 [penwidth=1, color=black];\n\t490 -> 285 [penwidth=1, color=black];\n\t490 -> 288 [penwidth=1, color=black];\n\t490 -> 1373 [penwidth=1, color=black];\n\t490 -> 1433 [penwidth=1, color=black];\n\t490 -> 1435 [penwidth=\"2.09861228866811\", color=black];\n\t491 -> 95 [penwidth=1, color=black];\n\t491 -> 102 [penwidth=1, color=black];\n\t491 -> 231 [penwidth=1, color=black];\n\t491 -> 238 [penwidth=1, color=black];\n\t491 -> 318 [penwidth=1, color=black];\n\t491 -> 332 [penwidth=1, color=black];\n\t491 -> 378 [penwidth=1, color=black];\n\t491 -> 380 [penwidth=1, color=black];\n\t491 -> 1435 [penwidth=\"3.0794415416798357\", color=black];\n\t492 -> 299 [penwidth=1, color=black];\n\t492 -> 1373 [penwidth=1, color=black];\n\t492 -> 1376 [penwidth=1, color=black];\n\t492 -> 1394 [penwidth=1, color=black];\n\t493 -> 300 [penwidth=1, color=black];\n\t493 -> 356 [penwidth=1, color=black];\n\t493 -> 358 [penwidth=1, color=black];\n\t494 -> 151 [penwidth=\"1.6931471805599454\", color=black];\n\t494 -> 260 [penwidth=\"1.6931471805599454\", color=black];\n\t494 -> 268 [penwidth=\"1.6931471805599454\", color=black];\n\t494 -> 1373 [penwidth=1, color=black];\n\t494 -> 1435 [penwidth=\"2.09861228866811\", color=black];\n\t494 -> 1871 [penwidth=1, color=black];\n\t495 -> 169 [penwidth=1, color=black];\n\t495 -> 170 [penwidth=1, color=black];\n\t495 -> 171 [penwidth=1, color=black];\n\t495 -> 172 [penwidth=1, color=black];\n\t495 -> 1435 [penwidth=\"2.386294361119891\", color=black];\n\t496 -> 247 [penwidth=1, color=black];\n\t496 -> 250 [penwidth=1, color=black];\n\t496 -> 335 [penwidth=1, color=black];\n\t496 -> 349 [penwidth=1, color=black];\n\t496 -> 355 [penwidth=1, color=black];\n\t496 -> 1435 [penwidth=\"2.6094379124341005\", color=black];\n\t497 -> 89 [penwidth=1, color=black];\n\t497 -> 90 [penwidth=1, color=black];\n\t497 -> 116 [penwidth=1, color=black];\n\t497 -> 150 [penwidth=1, color=black];\n\t497 -> 156 [penwidth=1, color=black];\n\t497 -> 1435 [penwidth=\"2.386294361119891\", color=black];\n\t498 -> 152 [penwidth=1, color=black];\n\t498 -> 161 [penwidth=1, color=black];\n\t498 -> 225 [penwidth=1, color=black];\n\t498 -> 304 [penwidth=1, color=black];\n\t498 -> 465 [penwidth=\"2.09861228866811\", color=black];\n\t498 -> 1350 [penwidth=1, color=black];\n\t498 -> 1392 [penwidth=1, color=black];\n\t498 -> 1393 [penwidth=1, color=black];\n\t498 -> 1440 [penwidth=1, color=black];\n\t499 -> 322 [penwidth=1, color=black];\n\t499 -> 464 [penwidth=\"1.6931471805599454\", color=black];\n\t499 -> 1375 [penwidth=1, color=black];\n\t500 -> 198 [penwidth=1, color=black];\n\t500 -> 264 [penwidth=1, color=black];\n\t500 -> 270 [penwidth=1, color=black];\n\t500 -> 1383 [penwidth=1, color=black];\n\t500 -> 1871 [penwidth=1, color=black];\n\t501 -> 311 [penwidth=1, color=black];\n\t501 -> 325 [penwidth=1, color=black];\n\t501 -> 341 [penwidth=1, color=black];\n\t501 -> 1435 [penwidth=\"2.09861228866811\", color=black];\n\t502 -> 153 [penwidth=1, color=black];\n\t502 -> 155 [penwidth=1, color=black];\n\t502 -> 157 [penwidth=1, color=black];\n\t502 -> 261 [penwidth=1, color=black];\n\t502 -> 387 [penwidth=1, color=black];\n\t502 -> 1435 [penwidth=\"2.6094379124341005\", color=black];\n\t503 -> 100 [penwidth=1, color=black];\n\t503 -> 101 [penwidth=1, color=black];\n\t503 -> 106 [penwidth=1, color=black];\n\t503 -> 112 [penwidth=1, color=black];\n\t503 -> 129 [penwidth=1, color=black];\n\t503 -> 139 [penwidth=1, color=black];\n\t503 -> 140 [penwidth=1, color=black];\n\t503 -> 147 [penwidth=1, color=black];\n\t503 -> 148 [penwidth=1, color=black];\n\t503 -> 162 [penwidth=1, color=black];\n\t503 -> 183 [penwidth=1, color=black];\n\t503 -> 186 [penwidth=1, color=black];\n\t503 -> 192 [penwidth=1, color=black];\n\t503 -> 193 [penwidth=1, color=black];\n\t503 -> 194 [penwidth=1, color=black];\n\t503 -> 240 [penwidth=1, color=black];\n\t503 -> 241 [penwidth=1, color=black];\n\t503 -> 242 [penwidth=1, color=black];\n\t503 -> 243 [penwidth=1, color=black];\n\t503 -> 271 [penwidth=1, color=black];\n\t503 -> 274 [penwidth=1, color=black];\n\t503 -> 292 [penwidth=1, color=black];\n\t503 -> 295 [penwidth=1, color=black];\n\t503 -> 298 [penwidth=1, color=black];\n\t503 -> 301 [penwidth=1, color=black];\n\t503 -> 303 [penwidth=1, color=black];\n\t503 -> 320 [penwidth=1, color=black];\n\t503 -> 343 [penwidth=1, color=black];\n\t503 -> 369 [penwidth=1, color=black];\n\t503 -> 381 [penwidth=1, color=black];\n\t503 -> 382 [penwidth=1, color=black];\n\t503 -> 384 [penwidth=1, color=black];\n\t503 -> 1435 [penwidth=\"4.401197381662156\", color=black];\n\t503 -> 1436 [penwidth=\"1.6931471805599454\", color=black];\n\t504 -> 91 [penwidth=1, color=black];\n\t504 -> 174 [penwidth=1, color=black];\n\t504 -> 262 [penwidth=1, color=black];\n\t504 -> 306 [penwidth=1, color=black];\n\t504 -> 310 [penwidth=1, color=black];\n\t504 -> 360 [penwidth=1, color=black];\n\t504 -> 383 [penwidth=1, color=black];\n\t504 -> 1435 [penwidth=\"2.9459101490553135\", color=black];\n\t505 -> 356 [penwidth=1, color=black];\n\t505 -> 1373 [penwidth=1, color=black];\n\t505 -> 1378 [penwidth=1, color=black];\n\t505 -> 1394 [penwidth=1, color=black];\n\t505 -> 1440 [penwidth=\"1.6931471805599454\", color=black];\n\t506 -> 362 [penwidth=1, color=black];\n\t506 -> 363 [penwidth=1, color=black];\n\t506 -> 364 [penwidth=1, color=black];\n\t507 -> 333 [penwidth=1, color=black];\n\t507 -> 457 [penwidth=1, color=black];\n\t507 -> 1439 [penwidth=1, color=black];\n\t508 -> 405 [penwidth=1, color=black];\n\t508 -> 466 [penwidth=1, color=black];\n\t509 -> 389 [penwidth=1, color=black];\n\t509 -> 390 [penwidth=1, color=black];\n\t509 -> 392 [penwidth=1, color=black];\n\t509 -> 1435 [penwidth=\"2.09861228866811\", color=black];\n\t510 -> 391 [penwidth=1, color=black];\n\t510 -> 1394 [penwidth=\"2.09861228866811\", color=black];\n\t511 -> 1440 [penwidth=1, color=black];\n\t512 -> 1373 [penwidth=1, color=black];\n\t512 -> 1442 [penwidth=\"1.6931471805599454\", color=black];\n\t513 -> 1373 [penwidth=1, color=black];\n\t514 -> 1394 [penwidth=1, color=black];\n\t515 -> 599 [penwidth=1, color=black];\n\t515 -> 1363 [penwidth=1, color=black];\n\t515 -> 1454 [penwidth=1, color=black];\n\t517 -> 85 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 86 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 87 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 88 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 93 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 94 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 104 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 105 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 108 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 109 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 110 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 111 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 113 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 117 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 118 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 121 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 123 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 125 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 126 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 130 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 131 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 132 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 133 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 134 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 141 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 143 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 144 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 145 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 149 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 154 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 160 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 163 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 164 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 165 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 166 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 167 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 175 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 176 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 177 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 178 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 179 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 180 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 181 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 182 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 188 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 189 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 190 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 202 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 205 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 207 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 212 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 213 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 214 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 215 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 216 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 217 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 218 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 219 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 220 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 221 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 222 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 223 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 224 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 226 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 227 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 228 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 229 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 230 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 233 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 234 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 235 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 239 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 245 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 246 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 248 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 249 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 251 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 252 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 253 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 259 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 265 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 269 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 272 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 273 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 276 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 277 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 278 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 279 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 280 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 282 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 287 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 289 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 290 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 291 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 293 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 294 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 296 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 297 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 305 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 308 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 309 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 312 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 313 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 314 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 315 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 319 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 323 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 324 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 327 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 329 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 330 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 334 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 336 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 337 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 340 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 342 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 344 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 345 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 347 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 348 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 350 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 351 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 352 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 354 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 359 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 361 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 366 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 367 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 370 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 371 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 372 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 373 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 374 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 375 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 376 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 379 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 385 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 386 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 388 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 394 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 395 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 396 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 398 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 399 [penwidth=\"1.6931471805599454\", color=black];\n\t517 -> 401 [penwidth=\"1.6931471805599454\", color=black];\n\t518 -> 412 [penwidth=1, color=black];\n\t518 -> 413 [penwidth=1, color=black];\n\t518 -> 417 [penwidth=1, color=black];\n\t518 -> 420 [penwidth=1, color=black];\n\t518 -> 435 [penwidth=1, color=black];\n\t518 -> 1435 [penwidth=\"2.6094379124341005\", color=black];\n\t519 -> 82 [penwidth=1, color=black];\n\t519 -> 377 [penwidth=1, color=black];\n\t519 -> 429 [penwidth=1, color=black];\n\t520 -> 316 [penwidth=1, color=black];\n\t520 -> 317 [penwidth=1, color=black];\n\t521 -> 122 [penwidth=1, color=black];\n\t521 -> 281 [penwidth=1, color=black];\n\t522 -> 258 [penwidth=1, color=black];\n\t523 -> 263 [penwidth=1, color=black];\n\t523 -> 400 [penwidth=1, color=black];\n\t524 -> 187 [penwidth=1, color=black];\n\t524 -> 321 [penwidth=1, color=black];\n\t524 -> 365 [penwidth=1, color=black];\n\t525 -> 210 [penwidth=1, color=black];\n\t526 -> 206 [penwidth=1, color=black];\n\t527 -> 208 [penwidth=1, color=black];\n\t529 -> 300 [penwidth=1, color=black];\n\t529 -> 358 [penwidth=1, color=black];\n\t530 -> 152 [penwidth=1, color=black];\n\t530 -> 516 [penwidth=1, color=black];\n\t530 -> 1463 [penwidth=1, color=black];\n\t532 -> 264 [penwidth=1, color=black];\n\t534 -> 333 [penwidth=1, color=black];\n\t535 -> 120 [penwidth=1, color=black];\n\t538 -> 225 [penwidth=1, color=black];\n\t542 -> 213 [penwidth=1, color=black];\n\t542 -> 365 [penwidth=1, color=black];\n\t543 -> 187 [penwidth=1, color=black];\n\t543 -> 213 [penwidth=1, color=black];\n\t544 -> 1266 [penwidth=1, color=black];\n\t545 -> 1268 [penwidth=1, color=black];\n\t547 -> 304 [penwidth=1, color=black];\n\t549 -> 213 [penwidth=1, color=black];\n\t549 -> 321 [penwidth=1, color=black];\n\t550 -> 159 [penwidth=1, color=black];\n\t550 -> 275 [penwidth=1, color=black];\n\t551 -> 84 [penwidth=1, color=black];\n\t552 -> 99 [penwidth=1, color=black];\n\t552 -> 119 [penwidth=1, color=black];\n\t552 -> 128 [penwidth=1, color=black];\n\t552 -> 137 [penwidth=1, color=black];\n\t552 -> 191 [penwidth=1, color=black];\n\t552 -> 254 [penwidth=1, color=black];\n\t552 -> 267 [penwidth=1, color=black];\n\t552 -> 377 [penwidth=1, color=black];\n\t552 -> 393 [penwidth=1, color=black];\n\t553 -> 98 [penwidth=1, color=black];\n\t553 -> 232 [penwidth=1, color=black];\n\t553 -> 328 [penwidth=1, color=black];\n\t554 -> 82 [penwidth=1, color=black];\n\t555 -> 316 [penwidth=1, color=black];\n\t555 -> 317 [penwidth=1, color=black];\n\t555 -> 1455 [penwidth=1, color=black];\n\t556 -> 85 [penwidth=1, color=black];\n\t556 -> 86 [penwidth=1, color=black];\n\t556 -> 87 [penwidth=1, color=black];\n\t556 -> 88 [penwidth=1, color=black];\n\t556 -> 93 [penwidth=1, color=black];\n\t556 -> 94 [penwidth=1, color=black];\n\t556 -> 104 [penwidth=1, color=black];\n\t556 -> 105 [penwidth=1, color=black];\n\t556 -> 108 [penwidth=1, color=black];\n\t556 -> 109 [penwidth=1, color=black];\n\t556 -> 110 [penwidth=1, color=black];\n\t556 -> 111 [penwidth=1, color=black];\n\t556 -> 113 [penwidth=1, color=black];\n\t556 -> 117 [penwidth=1, color=black];\n\t556 -> 118 [penwidth=1, color=black];\n\t556 -> 121 [penwidth=1, color=black];\n\t556 -> 123 [penwidth=1, color=black];\n\t556 -> 125 [penwidth=1, color=black];\n\t556 -> 126 [penwidth=1, color=black];\n\t556 -> 130 [penwidth=1, color=black];\n\t556 -> 131 [penwidth=1, color=black];\n\t556 -> 132 [penwidth=1, color=black];\n\t556 -> 133 [penwidth=1, color=black];\n\t556 -> 134 [penwidth=1, color=black];\n\t556 -> 141 [penwidth=1, color=black];\n\t556 -> 143 [penwidth=1, color=black];\n\t556 -> 144 [penwidth=1, color=black];\n\t556 -> 145 [penwidth=1, color=black];\n\t556 -> 149 [penwidth=1, color=black];\n\t556 -> 154 [penwidth=1, color=black];\n\t556 -> 160 [penwidth=1, color=black];\n\t556 -> 163 [penwidth=1, color=black];\n\t556 -> 164 [penwidth=1, color=black];\n\t556 -> 165 [penwidth=1, color=black];\n\t556 -> 166 [penwidth=1, color=black];\n\t556 -> 167 [penwidth=1, color=black];\n\t556 -> 175 [penwidth=1, color=black];\n\t556 -> 176 [penwidth=1, color=black];\n\t556 -> 177 [penwidth=1, color=black];\n\t556 -> 178 [penwidth=1, color=black];\n\t556 -> 179 [penwidth=1, color=black];\n\t556 -> 180 [penwidth=1, color=black];\n\t556 -> 181 [penwidth=1, color=black];\n\t556 -> 182 [penwidth=1, color=black];\n\t556 -> 188 [penwidth=1, color=black];\n\t556 -> 189 [penwidth=1, color=black];\n\t556 -> 190 [penwidth=1, color=black];\n\t556 -> 202 [penwidth=1, color=black];\n\t556 -> 205 [penwidth=1, color=black];\n\t556 -> 207 [penwidth=1, color=black];\n\t556 -> 212 [penwidth=1, color=black];\n\t556 -> 213 [penwidth=1, color=black];\n\t556 -> 214 [penwidth=1, color=black];\n\t556 -> 215 [penwidth=1, color=black];\n\t556 -> 216 [penwidth=1, color=black];\n\t556 -> 217 [penwidth=1, color=black];\n\t556 -> 218 [penwidth=1, color=black];\n\t556 -> 219 [penwidth=1, color=black];\n\t556 -> 220 [penwidth=1, color=black];\n\t556 -> 221 [penwidth=1, color=black];\n\t556 -> 222 [penwidth=1, color=black];\n\t556 -> 223 [penwidth=1, color=black];\n\t556 -> 224 [penwidth=1, color=black];\n\t556 -> 226 [penwidth=1, color=black];\n\t556 -> 227 [penwidth=1, color=black];\n\t556 -> 228 [penwidth=1, color=black];\n\t556 -> 229 [penwidth=1, color=black];\n\t556 -> 230 [penwidth=1, color=black];\n\t556 -> 233 [penwidth=1, color=black];\n\t556 -> 234 [penwidth=1, color=black];\n\t556 -> 235 [penwidth=1, color=black];\n\t556 -> 239 [penwidth=1, color=black];\n\t556 -> 245 [penwidth=1, color=black];\n\t556 -> 246 [penwidth=1, color=black];\n\t556 -> 248 [penwidth=1, color=black];\n\t556 -> 249 [penwidth=1, color=black];\n\t556 -> 251 [penwidth=1, color=black];\n\t556 -> 252 [penwidth=1, color=black];\n\t556 -> 253 [penwidth=1, color=black];\n\t556 -> 259 [penwidth=1, color=black];\n\t556 -> 265 [penwidth=1, color=black];\n\t556 -> 269 [penwidth=1, color=black];\n\t556 -> 272 [penwidth=1, color=black];\n\t556 -> 273 [penwidth=1, color=black];\n\t556 -> 276 [penwidth=1, color=black];\n\t556 -> 277 [penwidth=1, color=black];\n\t556 -> 278 [penwidth=1, color=black];\n\t556 -> 279 [penwidth=1, color=black];\n\t556 -> 280 [penwidth=1, color=black];\n\t556 -> 282 [penwidth=1, color=black];\n\t556 -> 287 [penwidth=1, color=black];\n\t556 -> 289 [penwidth=1, color=black];\n\t556 -> 290 [penwidth=1, color=black];\n\t556 -> 291 [penwidth=1, color=black];\n\t556 -> 293 [penwidth=1, color=black];\n\t556 -> 294 [penwidth=1, color=black];\n\t556 -> 296 [penwidth=1, color=black];\n\t556 -> 297 [penwidth=1, color=black];\n\t556 -> 305 [penwidth=1, color=black];\n\t556 -> 308 [penwidth=1, color=black];\n\t556 -> 309 [penwidth=1, color=black];\n\t556 -> 312 [penwidth=1, color=black];\n\t556 -> 313 [penwidth=1, color=black];\n\t556 -> 314 [penwidth=1, color=black];\n\t556 -> 315 [penwidth=1, color=black];\n\t556 -> 319 [penwidth=1, color=black];\n\t556 -> 323 [penwidth=1, color=black];\n\t556 -> 324 [penwidth=1, color=black];\n\t556 -> 327 [penwidth=1, color=black];\n\t556 -> 329 [penwidth=1, color=black];\n\t556 -> 330 [penwidth=1, color=black];\n\t556 -> 334 [penwidth=1, color=black];\n\t556 -> 336 [penwidth=1, color=black];\n\t556 -> 337 [penwidth=1, color=black];\n\t556 -> 340 [penwidth=1, color=black];\n\t556 -> 342 [penwidth=1, color=black];\n\t556 -> 344 [penwidth=1, color=black];\n\t556 -> 345 [penwidth=1, color=black];\n\t556 -> 347 [penwidth=1, color=black];\n\t556 -> 348 [penwidth=1, color=black];\n\t556 -> 350 [penwidth=1, color=black];\n\t556 -> 351 [penwidth=1, color=black];\n\t556 -> 352 [penwidth=1, color=black];\n\t556 -> 354 [penwidth=1, color=black];\n\t556 -> 359 [penwidth=1, color=black];\n\t556 -> 361 [penwidth=1, color=black];\n\t556 -> 366 [penwidth=1, color=black];\n\t556 -> 367 [penwidth=1, color=black];\n\t556 -> 370 [penwidth=1, color=black];\n\t556 -> 371 [penwidth=1, color=black];\n\t556 -> 372 [penwidth=1, color=black];\n\t556 -> 373 [penwidth=1, color=black];\n\t556 -> 374 [penwidth=1, color=black];\n\t556 -> 375 [penwidth=1, color=black];\n\t556 -> 376 [penwidth=1, color=black];\n\t556 -> 379 [penwidth=1, color=black];\n\t556 -> 385 [penwidth=1, color=black];\n\t556 -> 386 [penwidth=1, color=black];\n\t556 -> 388 [penwidth=1, color=black];\n\t556 -> 394 [penwidth=1, color=black];\n\t556 -> 395 [penwidth=1, color=black];\n\t556 -> 396 [penwidth=1, color=black];\n\t556 -> 398 [penwidth=1, color=black];\n\t556 -> 399 [penwidth=1, color=black];\n\t556 -> 401 [penwidth=1, color=black];\n\t556 -> 1464 [penwidth=\"5.969813299576001\", color=black];\n\t557 -> 173 [penwidth=1, color=black];\n\t557 -> 237 [penwidth=1, color=black];\n\t557 -> 255 [penwidth=1, color=black];\n\t558 -> 142 [penwidth=1, color=black];\n\t558 -> 185 [penwidth=1, color=black];\n\t558 -> 256 [penwidth=1, color=black];\n\t559 -> 122 [penwidth=1, color=black];\n\t559 -> 281 [penwidth=1, color=black];\n\t560 -> 92 [penwidth=1, color=black];\n\t560 -> 97 [penwidth=1, color=black];\n\t560 -> 168 [penwidth=1, color=black];\n\t560 -> 257 [penwidth=1, color=black];\n\t561 -> 114 [penwidth=1, color=black];\n\t561 -> 236 [penwidth=1, color=black];\n\t561 -> 258 [penwidth=1, color=black];\n\t561 -> 302 [penwidth=1, color=black];\n\t561 -> 357 [penwidth=1, color=black];\n\t562 -> 263 [penwidth=1, color=black];\n\t562 -> 400 [penwidth=1, color=black];\n\t563 -> 199 [penwidth=1, color=black];\n\t563 -> 200 [penwidth=1, color=black];\n\t563 -> 201 [penwidth=1, color=black];\n\t564 -> 187 [penwidth=1, color=black];\n\t564 -> 321 [penwidth=1, color=black];\n\t564 -> 365 [penwidth=1, color=black];\n\t564 -> 1454 [penwidth=1, color=black];\n\t565 -> 83 [penwidth=1, color=black];\n\t565 -> 209 [penwidth=1, color=black];\n\t565 -> 210 [penwidth=1, color=black];\n\t566 -> 206 [penwidth=1, color=black];\n\t567 -> 208 [penwidth=1, color=black];\n\t567 -> 211 [penwidth=1, color=black];\n\t567 -> 409 [penwidth=1, color=black];\n\t568 -> 184 [penwidth=1, color=black];\n\t568 -> 196 [penwidth=1, color=black];\n\t568 -> 203 [penwidth=1, color=black];\n\t568 -> 244 [penwidth=1, color=black];\n\t569 -> 107 [penwidth=1, color=black];\n\t569 -> 346 [penwidth=1, color=black];\n\t569 -> 368 [penwidth=1, color=black];\n\t570 -> 103 [penwidth=1, color=black];\n\t570 -> 146 [penwidth=1, color=black];\n\t570 -> 266 [penwidth=1, color=black];\n\t571 -> 115 [penwidth=1, color=black];\n\t571 -> 197 [penwidth=1, color=black];\n\t571 -> 204 [penwidth=1, color=black];\n\t571 -> 307 [penwidth=1, color=black];\n\t571 -> 326 [penwidth=1, color=black];\n\t571 -> 338 [penwidth=1, color=black];\n\t571 -> 339 [penwidth=1, color=black];\n\t571 -> 397 [penwidth=1, color=black];\n\t572 -> 135 [penwidth=1, color=black];\n\t572 -> 136 [penwidth=1, color=black];\n\t572 -> 286 [penwidth=1, color=black];\n\t573 -> 283 [penwidth=1, color=black];\n\t573 -> 284 [penwidth=1, color=black];\n\t573 -> 285 [penwidth=1, color=black];\n\t573 -> 288 [penwidth=1, color=black];\n\t574 -> 95 [penwidth=1, color=black];\n\t574 -> 102 [penwidth=1, color=black];\n\t574 -> 231 [penwidth=1, color=black];\n\t574 -> 238 [penwidth=1, color=black];\n\t574 -> 318 [penwidth=1, color=black];\n\t574 -> 332 [penwidth=1, color=black];\n\t574 -> 378 [penwidth=1, color=black];\n\t574 -> 380 [penwidth=1, color=black];\n\t575 -> 299 [penwidth=1, color=black];\n\t575 -> 1455 [penwidth=1, color=black];\n\t575 -> 1871 [penwidth=1, color=black];\n\t576 -> 300 [penwidth=1, color=black];\n\t576 -> 358 [penwidth=1, color=black];\n\t577 -> 151 [penwidth=1, color=black];\n\t577 -> 260 [penwidth=1, color=black];\n\t577 -> 268 [penwidth=1, color=black];\n\t578 -> 169 [penwidth=1, color=black];\n\t578 -> 170 [penwidth=1, color=black];\n\t578 -> 171 [penwidth=1, color=black];\n\t578 -> 172 [penwidth=1, color=black];\n\t579 -> 247 [penwidth=1, color=black];\n\t579 -> 250 [penwidth=1, color=black];\n\t579 -> 335 [penwidth=1, color=black];\n\t579 -> 349 [penwidth=1, color=black];\n\t579 -> 355 [penwidth=1, color=black];\n\t580 -> 89 [penwidth=1, color=black];\n\t580 -> 90 [penwidth=1, color=black];\n\t580 -> 116 [penwidth=1, color=black];\n\t580 -> 150 [penwidth=1, color=black];\n\t580 -> 156 [penwidth=1, color=black];\n\t581 -> 152 [penwidth=1, color=black];\n\t581 -> 161 [penwidth=1, color=black];\n\t581 -> 225 [penwidth=1, color=black];\n\t581 -> 304 [penwidth=1, color=black];\n\t581 -> 515 [penwidth=\"1.6931471805599454\", color=black];\n\t581 -> 599 [penwidth=\"1.6931471805599454\", color=black];\n\t582 -> 322 [penwidth=1, color=black];\n\t582 -> 1455 [penwidth=1, color=black];\n\t583 -> 198 [penwidth=1, color=black];\n\t583 -> 264 [penwidth=1, color=black];\n\t583 -> 270 [penwidth=1, color=black];\n\t584 -> 311 [penwidth=1, color=black];\n\t584 -> 325 [penwidth=1, color=black];\n\t584 -> 341 [penwidth=1, color=black];\n\t585 -> 153 [penwidth=1, color=black];\n\t585 -> 155 [penwidth=1, color=black];\n\t585 -> 157 [penwidth=1, color=black];\n\t585 -> 261 [penwidth=1, color=black];\n\t585 -> 387 [penwidth=1, color=black];\n\t586 -> 100 [penwidth=1, color=black];\n\t586 -> 101 [penwidth=1, color=black];\n\t586 -> 106 [penwidth=1, color=black];\n\t586 -> 112 [penwidth=1, color=black];\n\t586 -> 129 [penwidth=1, color=black];\n\t586 -> 139 [penwidth=1, color=black];\n\t586 -> 140 [penwidth=1, color=black];\n\t586 -> 147 [penwidth=1, color=black];\n\t586 -> 148 [penwidth=1, color=black];\n\t586 -> 162 [penwidth=1, color=black];\n\t586 -> 183 [penwidth=1, color=black];\n\t586 -> 186 [penwidth=1, color=black];\n\t586 -> 192 [penwidth=1, color=black];\n\t586 -> 193 [penwidth=1, color=black];\n\t586 -> 194 [penwidth=1, color=black];\n\t586 -> 240 [penwidth=1, color=black];\n\t586 -> 241 [penwidth=1, color=black];\n\t586 -> 242 [penwidth=1, color=black];\n\t586 -> 243 [penwidth=1, color=black];\n\t586 -> 271 [penwidth=1, color=black];\n\t586 -> 274 [penwidth=1, color=black];\n\t586 -> 292 [penwidth=1, color=black];\n\t586 -> 295 [penwidth=1, color=black];\n\t586 -> 298 [penwidth=1, color=black];\n\t586 -> 301 [penwidth=1, color=black];\n\t586 -> 303 [penwidth=1, color=black];\n\t586 -> 320 [penwidth=1, color=black];\n\t586 -> 343 [penwidth=1, color=black];\n\t586 -> 369 [penwidth=1, color=black];\n\t586 -> 381 [penwidth=1, color=black];\n\t586 -> 382 [penwidth=1, color=black];\n\t586 -> 384 [penwidth=1, color=black];\n\t587 -> 91 [penwidth=1, color=black];\n\t587 -> 174 [penwidth=1, color=black];\n\t587 -> 262 [penwidth=1, color=black];\n\t587 -> 306 [penwidth=1, color=black];\n\t587 -> 310 [penwidth=1, color=black];\n\t587 -> 360 [penwidth=1, color=black];\n\t587 -> 383 [penwidth=1, color=black];\n\t588 -> 356 [penwidth=1, color=black];\n\t588 -> 1455 [penwidth=1, color=black];\n\t589 -> 362 [penwidth=1, color=black];\n\t589 -> 363 [penwidth=1, color=black];\n\t589 -> 364 [penwidth=1, color=black];\n\t590 -> 333 [penwidth=1, color=black];\n\t591 -> 96 [penwidth=1, color=black];\n\t591 -> 120 [penwidth=1, color=black];\n\t591 -> 124 [penwidth=1, color=black];\n\t591 -> 127 [penwidth=1, color=black];\n\t591 -> 138 [penwidth=1, color=black];\n\t591 -> 158 [penwidth=1, color=black];\n\t591 -> 195 [penwidth=1, color=black];\n\t591 -> 331 [penwidth=1, color=black];\n\t591 -> 353 [penwidth=1, color=black];\n\t592 -> 389 [penwidth=1, color=black];\n\t592 -> 390 [penwidth=1, color=black];\n\t592 -> 392 [penwidth=1, color=black];\n\t593 -> 414 [penwidth=1, color=black];\n\t593 -> 416 [penwidth=1, color=black];\n\t593 -> 606 [penwidth=1, color=black];\n\t593 -> 610 [penwidth=1, color=black];\n\t594 -> 409 [penwidth=1, color=black];\n\t599 -> 516 [penwidth=1, color=black];\n\t599 -> 1483 [penwidth=1, color=black];\n\t600 -> 94 [penwidth=1, color=black];\n\t600 -> 109 [penwidth=1, color=black];\n\t600 -> 110 [penwidth=1, color=black];\n\t600 -> 154 [penwidth=1, color=black];\n\t600 -> 163 [penwidth=1, color=black];\n\t600 -> 164 [penwidth=1, color=black];\n\t600 -> 167 [penwidth=1, color=black];\n\t600 -> 202 [penwidth=1, color=black];\n\t600 -> 207 [penwidth=1, color=black];\n\t600 -> 213 [penwidth=1, color=black];\n\t600 -> 220 [penwidth=1, color=black];\n\t600 -> 221 [penwidth=1, color=black];\n\t600 -> 259 [penwidth=1, color=black];\n\t600 -> 293 [penwidth=1, color=black];\n\t600 -> 294 [penwidth=1, color=black];\n\t600 -> 296 [penwidth=1, color=black];\n\t600 -> 312 [penwidth=1, color=black];\n\t600 -> 354 [penwidth=1, color=black];\n\t600 -> 366 [penwidth=1, color=black];\n\t600 -> 376 [penwidth=1, color=black];\n\t600 -> 379 [penwidth=1, color=black];\n\t600 -> 386 [penwidth=1, color=black];\n\t600 -> 388 [penwidth=1, color=black];\n\t601 -> 85 [penwidth=1, color=black];\n\t601 -> 86 [penwidth=1, color=black];\n\t601 -> 87 [penwidth=1, color=black];\n\t601 -> 109 [penwidth=1, color=black];\n\t601 -> 110 [penwidth=1, color=black];\n\t601 -> 111 [penwidth=1, color=black];\n\t601 -> 118 [penwidth=1, color=black];\n\t601 -> 125 [penwidth=1, color=black];\n\t601 -> 132 [penwidth=1, color=black];\n\t601 -> 143 [penwidth=1, color=black];\n\t601 -> 144 [penwidth=1, color=black];\n\t601 -> 145 [penwidth=1, color=black];\n\t601 -> 163 [penwidth=1, color=black];\n\t601 -> 164 [penwidth=1, color=black];\n\t601 -> 167 [penwidth=1, color=black];\n\t601 -> 176 [penwidth=1, color=black];\n\t601 -> 177 [penwidth=1, color=black];\n\t601 -> 178 [penwidth=1, color=black];\n\t601 -> 179 [penwidth=1, color=black];\n\t601 -> 180 [penwidth=1, color=black];\n\t601 -> 181 [penwidth=1, color=black];\n\t601 -> 188 [penwidth=1, color=black];\n\t601 -> 205 [penwidth=1, color=black];\n\t601 -> 207 [penwidth=1, color=black];\n\t601 -> 212 [penwidth=1, color=black];\n\t601 -> 213 [penwidth=1, color=black];\n\t601 -> 214 [penwidth=1, color=black];\n\t601 -> 215 [penwidth=1, color=black];\n\t601 -> 216 [penwidth=1, color=black];\n\t601 -> 217 [penwidth=1, color=black];\n\t601 -> 218 [penwidth=1, color=black];\n\t601 -> 219 [penwidth=1, color=black];\n\t601 -> 222 [penwidth=1, color=black];\n\t601 -> 223 [penwidth=1, color=black];\n\t601 -> 224 [penwidth=1, color=black];\n\t601 -> 227 [penwidth=1, color=black];\n\t601 -> 233 [penwidth=1, color=black];\n\t601 -> 249 [penwidth=1, color=black];\n\t601 -> 259 [penwidth=1, color=black];\n\t601 -> 294 [penwidth=1, color=black];\n\t601 -> 305 [penwidth=1, color=black];\n\t601 -> 334 [penwidth=1, color=black];\n\t601 -> 336 [penwidth=1, color=black];\n\t601 -> 347 [penwidth=1, color=black];\n\t601 -> 366 [penwidth=1, color=black];\n\t601 -> 370 [penwidth=1, color=black];\n\t601 -> 371 [penwidth=1, color=black];\n\t601 -> 372 [penwidth=1, color=black];\n\t601 -> 373 [penwidth=1, color=black];\n\t601 -> 374 [penwidth=1, color=black];\n\t601 -> 375 [penwidth=1, color=black];\n\t601 -> 376 [penwidth=1, color=black];\n\t601 -> 379 [penwidth=1, color=black];\n\t601 -> 386 [penwidth=1, color=black];\n\t601 -> 388 [penwidth=1, color=black];\n\t601 -> 398 [penwidth=1, color=black];\n\t602 -> 88 [penwidth=1, color=black];\n\t602 -> 93 [penwidth=1, color=black];\n\t602 -> 94 [penwidth=1, color=black];\n\t602 -> 104 [penwidth=1, color=black];\n\t602 -> 105 [penwidth=1, color=black];\n\t602 -> 108 [penwidth=1, color=black];\n\t602 -> 110 [penwidth=1, color=black];\n\t602 -> 111 [penwidth=1, color=black];\n\t602 -> 113 [penwidth=1, color=black];\n\t602 -> 117 [penwidth=1, color=black];\n\t602 -> 121 [penwidth=1, color=black];\n\t602 -> 123 [penwidth=1, color=black];\n\t602 -> 126 [penwidth=1, color=black];\n\t602 -> 130 [penwidth=1, color=black];\n\t602 -> 131 [penwidth=1, color=black];\n\t602 -> 133 [penwidth=1, color=black];\n\t602 -> 141 [penwidth=1, color=black];\n\t602 -> 149 [penwidth=1, color=black];\n\t602 -> 163 [penwidth=1, color=black];\n\t602 -> 164 [penwidth=1, color=black];\n\t602 -> 165 [penwidth=1, color=black];\n\t602 -> 166 [penwidth=1, color=black];\n\t602 -> 167 [penwidth=1, color=black];\n\t602 -> 188 [penwidth=1, color=black];\n\t602 -> 202 [penwidth=1, color=black];\n\t602 -> 207 [penwidth=1, color=black];\n\t602 -> 213 [penwidth=1, color=black];\n\t602 -> 220 [penwidth=1, color=black];\n\t602 -> 221 [penwidth=1, color=black];\n\t602 -> 226 [penwidth=1, color=black];\n\t602 -> 228 [penwidth=1, color=black];\n\t602 -> 229 [penwidth=1, color=black];\n\t602 -> 230 [penwidth=1, color=black];\n\t602 -> 234 [penwidth=1, color=black];\n\t602 -> 235 [penwidth=1, color=black];\n\t602 -> 239 [penwidth=1, color=black];\n\t602 -> 245 [penwidth=1, color=black];\n\t602 -> 246 [penwidth=1, color=black];\n\t602 -> 248 [penwidth=1, color=black];\n\t602 -> 251 [penwidth=1, color=black];\n\t602 -> 252 [penwidth=1, color=black];\n\t602 -> 253 [penwidth=1, color=black];\n\t602 -> 259 [penwidth=1, color=black];\n\t602 -> 265 [penwidth=1, color=black];\n\t602 -> 269 [penwidth=1, color=black];\n\t602 -> 272 [penwidth=1, color=black];\n\t602 -> 273 [penwidth=1, color=black];\n\t602 -> 276 [penwidth=1, color=black];\n\t602 -> 278 [penwidth=1, color=black];\n\t602 -> 279 [penwidth=1, color=black];\n\t602 -> 280 [penwidth=1, color=black];\n\t602 -> 282 [penwidth=1, color=black];\n\t602 -> 287 [penwidth=1, color=black];\n\t602 -> 289 [penwidth=1, color=black];\n\t602 -> 290 [penwidth=1, color=black];\n\t602 -> 291 [penwidth=1, color=black];\n\t602 -> 308 [penwidth=1, color=black];\n\t602 -> 309 [penwidth=1, color=black];\n\t602 -> 313 [penwidth=1, color=black];\n\t602 -> 314 [penwidth=1, color=black];\n\t602 -> 315 [penwidth=1, color=black];\n\t602 -> 319 [penwidth=1, color=black];\n\t602 -> 327 [penwidth=1, color=black];\n\t602 -> 329 [penwidth=1, color=black];\n\t602 -> 330 [penwidth=1, color=black];\n\t602 -> 340 [penwidth=1, color=black];\n\t602 -> 342 [penwidth=1, color=black];\n\t602 -> 347 [penwidth=1, color=black];\n\t602 -> 350 [penwidth=1, color=black];\n\t602 -> 352 [penwidth=1, color=black];\n\t602 -> 354 [penwidth=1, color=black];\n\t602 -> 359 [penwidth=1, color=black];\n\t602 -> 361 [penwidth=1, color=black];\n\t602 -> 367 [penwidth=1, color=black];\n\t602 -> 376 [penwidth=1, color=black];\n\t602 -> 385 [penwidth=1, color=black];\n\t602 -> 386 [penwidth=1, color=black];\n\t602 -> 388 [penwidth=1, color=black];\n\t602 -> 395 [penwidth=1, color=black];\n\t602 -> 396 [penwidth=1, color=black];\n\t603 -> 109 [penwidth=1, color=black];\n\t603 -> 110 [penwidth=1, color=black];\n\t603 -> 111 [penwidth=1, color=black];\n\t603 -> 134 [penwidth=1, color=black];\n\t603 -> 154 [penwidth=1, color=black];\n\t603 -> 160 [penwidth=1, color=black];\n\t603 -> 163 [penwidth=1, color=black];\n\t603 -> 164 [penwidth=1, color=black];\n\t603 -> 167 [penwidth=1, color=black];\n\t603 -> 175 [penwidth=1, color=black];\n\t603 -> 182 [penwidth=1, color=black];\n\t603 -> 188 [penwidth=1, color=black];\n\t603 -> 189 [penwidth=1, color=black];\n\t603 -> 190 [penwidth=1, color=black];\n\t603 -> 213 [penwidth=1, color=black];\n\t603 -> 221 [penwidth=1, color=black];\n\t603 -> 227 [penwidth=1, color=black];\n\t603 -> 245 [penwidth=1, color=black];\n\t603 -> 259 [penwidth=1, color=black];\n\t603 -> 277 [penwidth=1, color=black];\n\t603 -> 294 [penwidth=1, color=black];\n\t603 -> 296 [penwidth=1, color=black];\n\t603 -> 297 [penwidth=1, color=black];\n\t603 -> 305 [penwidth=1, color=black];\n\t603 -> 323 [penwidth=1, color=black];\n\t603 -> 324 [penwidth=1, color=black];\n\t603 -> 329 [penwidth=1, color=black];\n\t603 -> 337 [penwidth=1, color=black];\n\t603 -> 344 [penwidth=1, color=black];\n\t603 -> 345 [penwidth=1, color=black];\n\t603 -> 347 [penwidth=1, color=black];\n\t603 -> 348 [penwidth=1, color=black];\n\t603 -> 351 [penwidth=1, color=black];\n\t603 -> 354 [penwidth=1, color=black];\n\t603 -> 366 [penwidth=1, color=black];\n\t603 -> 376 [penwidth=1, color=black];\n\t603 -> 379 [penwidth=1, color=black];\n\t603 -> 386 [penwidth=1, color=black];\n\t603 -> 388 [penwidth=1, color=black];\n\t603 -> 394 [penwidth=1, color=black];\n\t603 -> 399 [penwidth=1, color=black];\n\t603 -> 401 [penwidth=1, color=black];\n\t604 -> 312 [penwidth=1, color=black];\n\t604 -> 388 [penwidth=1, color=black];\n\t605 -> 82 [penwidth=1, color=black];\n\t605 -> 393 [penwidth=1, color=black];\n\t605 -> 429 [penwidth=1, color=black];\n\t1201 -> 1075 [penwidth=1, color=black];\n\t1201 -> 1168 [penwidth=1, color=black];\n\t1201 -> 1188 [penwidth=1, color=black];\n\t1201 -> 1207 [penwidth=1, color=black];\n\t1202 -> 1074 [penwidth=1, color=black];\n\t1204 -> 1226 [penwidth=1, color=chartreuse];\n\t1206 -> 644 [penwidth=1, color=black];\n\t1206 -> 1188 [penwidth=1, color=black];\n\t1208 -> 644 [penwidth=1, color=black];\n\t1208 -> 1188 [penwidth=1, color=black];\n\t1208 -> 1429 [penwidth=1, color=black];\n\t1209 -> 644 [penwidth=1, color=black];\n\t1209 -> 1188 [penwidth=1, color=black];\n\t1209 -> 1429 [penwidth=1, color=black];\n\t1210 -> 611 [penwidth=1, color=black];\n\t1210 -> 642 [penwidth=1, color=black];\n\t1210 -> 643 [penwidth=1, color=black];\n\t1210 -> 651 [penwidth=1, color=black];\n\t1210 -> 652 [penwidth=1, color=black];\n\t1210 -> 690 [penwidth=1, color=black];\n\t1210 -> 752 [penwidth=1, color=black];\n\t1210 -> 871 [penwidth=1, color=black];\n\t1210 -> 872 [penwidth=1, color=black];\n\t1210 -> 1018 [penwidth=1, color=black];\n\t1210 -> 1024 [penwidth=1, color=black];\n\t1210 -> 1025 [penwidth=1, color=black];\n\t1210 -> 1043 [penwidth=1, color=black];\n\t1210 -> 1044 [penwidth=1, color=black];\n\t1210 -> 1056 [penwidth=1, color=black];\n\t1210 -> 1063 [penwidth=1, color=black];\n\t1210 -> 1064 [penwidth=1, color=black];\n\t1210 -> 1065 [penwidth=1, color=black];\n\t1210 -> 1066 [penwidth=1, color=black];\n\t1210 -> 1067 [penwidth=1, color=black];\n\t1210 -> 1073 [penwidth=1, color=black];\n\t1210 -> 1076 [penwidth=1, color=black];\n\t1210 -> 1077 [penwidth=1, color=black];\n\t1210 -> 1078 [penwidth=1, color=black];\n\t1210 -> 1079 [penwidth=1, color=black];\n\t1210 -> 1080 [penwidth=1, color=black];\n\t1210 -> 1086 [penwidth=1, color=black];\n\t1210 -> 1114 [penwidth=1, color=black];\n\t1210 -> 1115 [penwidth=1, color=black];\n\t1210 -> 1116 [penwidth=1, color=black];\n\t1210 -> 1142 [penwidth=1, color=black];\n\t1210 -> 1195 [penwidth=1, color=black];\n\t1210 -> 1196 [penwidth=1, color=black];\n\t1210 -> 1197 [penwidth=1, color=black];\n\t1210 -> 1198 [penwidth=1, color=black];\n\t1210 -> 1435 [penwidth=\"4.555348061489413\", color=black];\n\t1211 -> 644 [penwidth=1, color=black];\n\t1211 -> 873 [penwidth=1, color=black];\n\t1211 -> 1074 [penwidth=1, color=black];\n\t1211 -> 1075 [penwidth=1, color=black];\n\t1211 -> 1188 [penwidth=1, color=black];\n\t1211 -> 1373 [penwidth=1, color=black];\n\t1211 -> 1433 [penwidth=1, color=black];\n\t1211 -> 1440 [penwidth=1, color=black];\n\t1212 -> 645 [penwidth=1, color=black];\n\t1212 -> 1187 [penwidth=1, color=black];\n\t1212 -> 1435 [penwidth=1, color=black];\n\t1213 -> 612 [penwidth=1, color=black];\n\t1213 -> 613 [penwidth=1, color=black];\n\t1213 -> 614 [penwidth=1, color=black];\n\t1213 -> 615 [penwidth=1, color=black];\n\t1213 -> 616 [penwidth=1, color=black];\n\t1213 -> 617 [penwidth=1, color=black];\n\t1213 -> 618 [penwidth=1, color=black];\n\t1213 -> 619 [penwidth=1, color=black];\n\t1213 -> 620 [penwidth=1, color=black];\n\t1213 -> 621 [penwidth=1, color=black];\n\t1213 -> 622 [penwidth=1, color=black];\n\t1213 -> 623 [penwidth=1, color=black];\n\t1213 -> 624 [penwidth=1, color=black];\n\t1213 -> 625 [penwidth=1, color=black];\n\t1213 -> 626 [penwidth=1, color=black];\n\t1213 -> 627 [penwidth=1, color=black];\n\t1213 -> 628 [penwidth=1, color=black];\n\t1213 -> 629 [penwidth=1, color=black];\n\t1213 -> 630 [penwidth=1, color=black];\n\t1213 -> 631 [penwidth=1, color=black];\n\t1213 -> 632 [penwidth=1, color=black];\n\t1213 -> 633 [penwidth=1, color=black];\n\t1213 -> 634 [penwidth=1, color=black];\n\t1213 -> 635 [penwidth=1, color=black];\n\t1213 -> 636 [penwidth=1, color=black];\n\t1213 -> 637 [penwidth=1, color=black];\n\t1213 -> 638 [penwidth=1, color=black];\n\t1213 -> 639 [penwidth=1, color=black];\n\t1213 -> 640 [penwidth=1, color=black];\n\t1213 -> 641 [penwidth=1, color=black];\n\t1213 -> 646 [penwidth=1, color=black];\n\t1213 -> 647 [penwidth=1, color=black];\n\t1213 -> 648 [penwidth=1, color=black];\n\t1213 -> 649 [penwidth=1, color=black];\n\t1213 -> 650 [penwidth=1, color=black];\n\t1213 -> 653 [penwidth=1, color=black];\n\t1213 -> 654 [penwidth=1, color=black];\n\t1213 -> 655 [penwidth=1, color=black];\n\t1213 -> 656 [penwidth=1, color=black];\n\t1213 -> 657 [penwidth=1, color=black];\n\t1213 -> 658 [penwidth=1, color=black];\n\t1213 -> 659 [penwidth=1, color=black];\n\t1213 -> 660 [penwidth=1, color=black];\n\t1213 -> 661 [penwidth=1, color=black];\n\t1213 -> 662 [penwidth=1, color=black];\n\t1213 -> 663 [penwidth=1, color=black];\n\t1213 -> 664 [penwidth=1, color=black];\n\t1213 -> 665 [penwidth=1, color=black];\n\t1213 -> 666 [penwidth=1, color=black];\n\t1213 -> 667 [penwidth=1, color=black];\n\t1213 -> 668 [penwidth=1, color=black];\n\t1213 -> 669 [penwidth=1, color=black];\n\t1213 -> 670 [penwidth=1, color=black];\n\t1213 -> 671 [penwidth=1, color=black];\n\t1213 -> 672 [penwidth=1, color=black];\n\t1213 -> 673 [penwidth=1, color=black];\n\t1213 -> 674 [penwidth=1, color=black];\n\t1213 -> 675 [penwidth=1, color=black];\n\t1213 -> 676 [penwidth=1, color=black];\n\t1213 -> 677 [penwidth=1, color=black];\n\t1213 -> 678 [penwidth=1, color=black];\n\t1213 -> 679 [penwidth=1, color=black];\n\t1213 -> 680 [penwidth=1, color=black];\n\t1213 -> 681 [penwidth=1, color=black];\n\t1213 -> 682 [penwidth=1, color=black];\n\t1213 -> 683 [penwidth=1, color=black];\n\t1213 -> 684 [penwidth=1, color=black];\n\t1213 -> 685 [penwidth=1, color=black];\n\t1213 -> 686 [penwidth=1, color=black];\n\t1213 -> 687 [penwidth=1, color=black];\n\t1213 -> 688 [penwidth=1, color=black];\n\t1213 -> 689 [penwidth=1, color=black];\n\t1213 -> 691 [penwidth=1, color=black];\n\t1213 -> 692 [penwidth=1, color=black];\n\t1213 -> 693 [penwidth=1, color=black];\n\t1213 -> 694 [penwidth=1, color=black];\n\t1213 -> 695 [penwidth=1, color=black];\n\t1213 -> 696 [penwidth=1, color=black];\n\t1213 -> 697 [penwidth=1, color=black];\n\t1213 -> 698 [penwidth=1, color=black];\n\t1213 -> 699 [penwidth=1, color=black];\n\t1213 -> 700 [penwidth=1, color=black];\n\t1213 -> 701 [penwidth=1, color=black];\n\t1213 -> 702 [penwidth=1, color=black];\n\t1213 -> 703 [penwidth=1, color=black];\n\t1213 -> 704 [penwidth=1, color=black];\n\t1213 -> 705 [penwidth=1, color=black];\n\t1213 -> 706 [penwidth=1, color=black];\n\t1213 -> 707 [penwidth=1, color=black];\n\t1213 -> 708 [penwidth=1, color=black];\n\t1213 -> 709 [penwidth=1, color=black];\n\t1213 -> 710 [penwidth=1, color=black];\n\t1213 -> 711 [penwidth=1, color=black];\n\t1213 -> 712 [penwidth=1, color=black];\n\t1213 -> 713 [penwidth=1, color=black];\n\t1213 -> 714 [penwidth=1, color=black];\n\t1213 -> 715 [penwidth=1, color=black];\n\t1213 -> 716 [penwidth=1, color=black];\n\t1213 -> 717 [penwidth=1, color=black];\n\t1213 -> 718 [penwidth=1, color=black];\n\t1213 -> 719 [penwidth=1, color=black];\n\t1213 -> 720 [penwidth=1, color=black];\n\t1213 -> 721 [penwidth=1, color=black];\n\t1213 -> 722 [penwidth=1, color=black];\n\t1213 -> 723 [penwidth=1, color=black];\n\t1213 -> 724 [penwidth=1, color=black];\n\t1213 -> 725 [penwidth=1, color=black];\n\t1213 -> 726 [penwidth=1, color=black];\n\t1213 -> 727 [penwidth=1, color=black];\n\t1213 -> 728 [penwidth=1, color=black];\n\t1213 -> 729 [penwidth=1, color=black];\n\t1213 -> 730 [penwidth=1, color=black];\n\t1213 -> 731 [penwidth=1, color=black];\n\t1213 -> 732 [penwidth=1, color=black];\n\t1213 -> 733 [penwidth=1, color=black];\n\t1213 -> 734 [penwidth=1, color=black];\n\t1213 -> 735 [penwidth=1, color=black];\n\t1213 -> 736 [penwidth=1, color=black];\n\t1213 -> 737 [penwidth=1, color=black];\n\t1213 -> 738 [penwidth=1, color=black];\n\t1213 -> 739 [penwidth=1, color=black];\n\t1213 -> 740 [penwidth=1, color=black];\n\t1213 -> 741 [penwidth=1, color=black];\n\t1213 -> 742 [penwidth=1, color=black];\n\t1213 -> 743 [penwidth=1, color=black];\n\t1213 -> 744 [penwidth=1, color=black];\n\t1213 -> 745 [penwidth=1, color=black];\n\t1213 -> 746 [penwidth=1, color=black];\n\t1213 -> 747 [penwidth=1, color=black];\n\t1213 -> 748 [penwidth=1, color=black];\n\t1213 -> 749 [penwidth=1, color=black];\n\t1213 -> 750 [penwidth=1, color=black];\n\t1213 -> 751 [penwidth=1, color=black];\n\t1213 -> 753 [penwidth=1, color=black];\n\t1213 -> 754 [penwidth=1, color=black];\n\t1213 -> 755 [penwidth=1, color=black];\n\t1213 -> 756 [penwidth=1, color=black];\n\t1213 -> 757 [penwidth=1, color=black];\n\t1213 -> 758 [penwidth=1, color=black];\n\t1213 -> 759 [penwidth=1, color=black];\n\t1213 -> 760 [penwidth=1, color=black];\n\t1213 -> 761 [penwidth=1, color=black];\n\t1213 -> 762 [penwidth=1, color=black];\n\t1213 -> 763 [penwidth=1, color=black];\n\t1213 -> 764 [penwidth=1, color=black];\n\t1213 -> 765 [penwidth=1, color=black];\n\t1213 -> 766 [penwidth=1, color=black];\n\t1213 -> 767 [penwidth=1, color=black];\n\t1213 -> 768 [penwidth=1, color=black];\n\t1213 -> 769 [penwidth=1, color=black];\n\t1213 -> 770 [penwidth=1, color=black];\n\t1213 -> 771 [penwidth=1, color=black];\n\t1213 -> 772 [penwidth=1, color=black];\n\t1213 -> 773 [penwidth=1, color=black];\n\t1213 -> 774 [penwidth=1, color=black];\n\t1213 -> 775 [penwidth=1, color=black];\n\t1213 -> 776 [penwidth=1, color=black];\n\t1213 -> 777 [penwidth=1, color=black];\n\t1213 -> 778 [penwidth=1, color=black];\n\t1213 -> 779 [penwidth=1, color=black];\n\t1213 -> 780 [penwidth=1, color=black];\n\t1213 -> 781 [penwidth=1, color=black];\n\t1213 -> 782 [penwidth=1, color=black];\n\t1213 -> 783 [penwidth=1, color=black];\n\t1213 -> 784 [penwidth=1, color=black];\n\t1213 -> 785 [penwidth=1, color=black];\n\t1213 -> 786 [penwidth=1, color=black];\n\t1213 -> 787 [penwidth=1, color=black];\n\t1213 -> 788 [penwidth=1, color=black];\n\t1213 -> 789 [penwidth=1, color=black];\n\t1213 -> 790 [penwidth=1, color=black];\n\t1213 -> 791 [penwidth=1, color=black];\n\t1213 -> 792 [penwidth=1, color=black];\n\t1213 -> 793 [penwidth=1, color=black];\n\t1213 -> 794 [penwidth=1, color=black];\n\t1213 -> 795 [penwidth=1, color=black];\n\t1213 -> 796 [penwidth=1, color=black];\n\t1213 -> 797 [penwidth=1, color=black];\n\t1213 -> 798 [penwidth=1, color=black];\n\t1213 -> 799 [penwidth=1, color=black];\n\t1213 -> 800 [penwidth=1, color=black];\n\t1213 -> 801 [penwidth=1, color=black];\n\t1213 -> 802 [penwidth=1, color=black];\n\t1213 -> 803 [penwidth=1, color=black];\n\t1213 -> 804 [penwidth=1, color=black];\n\t1213 -> 805 [penwidth=1, color=black];\n\t1213 -> 806 [penwidth=1, color=black];\n\t1213 -> 807 [penwidth=1, color=black];\n\t1213 -> 808 [penwidth=1, color=black];\n\t1213 -> 809 [penwidth=1, color=black];\n\t1213 -> 810 [penwidth=1, color=black];\n\t1213 -> 811 [penwidth=1, color=black];\n\t1213 -> 812 [penwidth=1, color=black];\n\t1213 -> 813 [penwidth=1, color=black];\n\t1213 -> 814 [penwidth=1, color=black];\n\t1213 -> 815 [penwidth=1, color=black];\n\t1213 -> 816 [penwidth=1, color=black];\n\t1213 -> 817 [penwidth=1, color=black];\n\t1213 -> 818 [penwidth=1, color=black];\n\t1213 -> 819 [penwidth=1, color=black];\n\t1213 -> 820 [penwidth=1, color=black];\n\t1213 -> 821 [penwidth=1, color=black];\n\t1213 -> 822 [penwidth=1, color=black];\n\t1213 -> 823 [penwidth=1, color=black];\n\t1213 -> 824 [penwidth=1, color=black];\n\t1213 -> 825 [penwidth=1, color=black];\n\t1213 -> 826 [penwidth=1, color=black];\n\t1213 -> 827 [penwidth=1, color=black];\n\t1213 -> 828 [penwidth=1, color=black];\n\t1213 -> 829 [penwidth=1, color=black];\n\t1213 -> 830 [penwidth=1, color=black];\n\t1213 -> 831 [penwidth=1, color=black];\n\t1213 -> 832 [penwidth=1, color=black];\n\t1213 -> 833 [penwidth=1, color=black];\n\t1213 -> 834 [penwidth=1, color=black];\n\t1213 -> 835 [penwidth=1, color=black];\n\t1213 -> 836 [penwidth=1, color=black];\n\t1213 -> 837 [penwidth=1, color=black];\n\t1213 -> 838 [penwidth=1, color=black];\n\t1213 -> 839 [penwidth=1, color=black];\n\t1213 -> 840 [penwidth=1, color=black];\n\t1213 -> 841 [penwidth=1, color=black];\n\t1213 -> 842 [penwidth=1, color=black];\n\t1213 -> 843 [penwidth=1, color=black];\n\t1213 -> 844 [penwidth=1, color=black];\n\t1213 -> 845 [penwidth=1, color=black];\n\t1213 -> 846 [penwidth=1, color=black];\n\t1213 -> 847 [penwidth=1, color=black];\n\t1213 -> 848 [penwidth=1, color=black];\n\t1213 -> 849 [penwidth=1, color=black];\n\t1213 -> 850 [penwidth=1, color=black];\n\t1213 -> 851 [penwidth=1, color=black];\n\t1213 -> 852 [penwidth=1, color=black];\n\t1213 -> 853 [penwidth=1, color=black];\n\t1213 -> 854 [penwidth=1, color=black];\n\t1213 -> 855 [penwidth=1, color=black];\n\t1213 -> 856 [penwidth=1, color=black];\n\t1213 -> 857 [penwidth=1, color=black];\n\t1213 -> 858 [penwidth=1, color=black];\n\t1213 -> 859 [penwidth=1, color=black];\n\t1213 -> 860 [penwidth=1, color=black];\n\t1213 -> 861 [penwidth=1, color=black];\n\t1213 -> 862 [penwidth=1, color=black];\n\t1213 -> 863 [penwidth=1, color=black];\n\t1213 -> 864 [penwidth=1, color=black];\n\t1213 -> 865 [penwidth=1, color=black];\n\t1213 -> 866 [penwidth=1, color=black];\n\t1213 -> 867 [penwidth=1, color=black];\n\t1213 -> 868 [penwidth=1, color=black];\n\t1213 -> 869 [penwidth=1, color=black];\n\t1213 -> 870 [penwidth=1, color=black];\n\t1213 -> 874 [penwidth=1, color=black];\n\t1213 -> 875 [penwidth=1, color=black];\n\t1213 -> 876 [penwidth=1, color=black];\n\t1213 -> 877 [penwidth=1, color=black];\n\t1213 -> 878 [penwidth=1, color=black];\n\t1213 -> 879 [penwidth=1, color=black];\n\t1213 -> 880 [penwidth=1, color=black];\n\t1213 -> 881 [penwidth=1, color=black];\n\t1213 -> 882 [penwidth=1, color=black];\n\t1213 -> 883 [penwidth=1, color=black];\n\t1213 -> 884 [penwidth=1, color=black];\n\t1213 -> 885 [penwidth=1, color=black];\n\t1213 -> 886 [penwidth=1, color=black];\n\t1213 -> 887 [penwidth=1, color=black];\n\t1213 -> 888 [penwidth=1, color=black];\n\t1213 -> 889 [penwidth=1, color=black];\n\t1213 -> 890 [penwidth=1, color=black];\n\t1213 -> 891 [penwidth=1, color=black];\n\t1213 -> 892 [penwidth=1, color=black];\n\t1213 -> 893 [penwidth=1, color=black];\n\t1213 -> 894 [penwidth=1, color=black];\n\t1213 -> 895 [penwidth=1, color=black];\n\t1213 -> 896 [penwidth=1, color=black];\n\t1213 -> 897 [penwidth=1, color=black];\n\t1213 -> 898 [penwidth=1, color=black];\n\t1213 -> 899 [penwidth=1, color=black];\n\t1213 -> 900 [penwidth=1, color=black];\n\t1213 -> 901 [penwidth=1, color=black];\n\t1213 -> 902 [penwidth=1, color=black];\n\t1213 -> 903 [penwidth=1, color=black];\n\t1213 -> 904 [penwidth=1, color=black];\n\t1213 -> 905 [penwidth=1, color=black];\n\t1213 -> 906 [penwidth=1, color=black];\n\t1213 -> 907 [penwidth=1, color=black];\n\t1213 -> 908 [penwidth=1, color=black];\n\t1213 -> 909 [penwidth=1, color=black];\n\t1213 -> 910 [penwidth=1, color=black];\n\t1213 -> 911 [penwidth=1, color=black];\n\t1213 -> 912 [penwidth=1, color=black];\n\t1213 -> 913 [penwidth=1, color=black];\n\t1213 -> 914 [penwidth=1, color=black];\n\t1213 -> 915 [penwidth=1, color=black];\n\t1213 -> 916 [penwidth=1, color=black];\n\t1213 -> 917 [penwidth=1, color=black];\n\t1213 -> 918 [penwidth=1, color=black];\n\t1213 -> 919 [penwidth=1, color=black];\n\t1213 -> 920 [penwidth=1, color=black];\n\t1213 -> 921 [penwidth=1, color=black];\n\t1213 -> 922 [penwidth=1, color=black];\n\t1213 -> 923 [penwidth=1, color=black];\n\t1213 -> 924 [penwidth=1, color=black];\n\t1213 -> 925 [penwidth=1, color=black];\n\t1213 -> 926 [penwidth=1, color=black];\n\t1213 -> 927 [penwidth=1, color=black];\n\t1213 -> 928 [penwidth=1, color=black];\n\t1213 -> 929 [penwidth=1, color=black];\n\t1213 -> 930 [penwidth=1, color=black];\n\t1213 -> 931 [penwidth=1, color=black];\n\t1213 -> 932 [penwidth=1, color=black];\n\t1213 -> 933 [penwidth=1, color=black];\n\t1213 -> 934 [penwidth=1, color=black];\n\t1213 -> 935 [penwidth=1, color=black];\n\t1213 -> 936 [penwidth=1, color=black];\n\t1213 -> 937 [penwidth=1, color=black];\n\t1213 -> 938 [penwidth=1, color=black];\n\t1213 -> 939 [penwidth=1, color=black];\n\t1213 -> 940 [penwidth=1, color=black];\n\t1213 -> 941 [penwidth=1, color=black];\n\t1213 -> 942 [penwidth=1, color=black];\n\t1213 -> 943 [penwidth=1, color=black];\n\t1213 -> 944 [penwidth=1, color=black];\n\t1213 -> 945 [penwidth=1, color=black];\n\t1213 -> 946 [penwidth=1, color=black];\n\t1213 -> 947 [penwidth=1, color=black];\n\t1213 -> 948 [penwidth=1, color=black];\n\t1213 -> 949 [penwidth=1, color=black];\n\t1213 -> 950 [penwidth=1, color=black];\n\t1213 -> 951 [penwidth=1, color=black];\n\t1213 -> 952 [penwidth=1, color=black];\n\t1213 -> 953 [penwidth=1, color=black];\n\t1213 -> 954 [penwidth=1, color=black];\n\t1213 -> 955 [penwidth=1, color=black];\n\t1213 -> 956 [penwidth=1, color=black];\n\t1213 -> 957 [penwidth=1, color=black];\n\t1213 -> 958 [penwidth=1, color=black];\n\t1213 -> 959 [penwidth=1, color=black];\n\t1213 -> 960 [penwidth=1, color=black];\n\t1213 -> 961 [penwidth=1, color=black];\n\t1213 -> 962 [penwidth=1, color=black];\n\t1213 -> 963 [penwidth=1, color=black];\n\t1213 -> 964 [penwidth=1, color=black];\n\t1213 -> 965 [penwidth=1, color=black];\n\t1213 -> 966 [penwidth=1, color=black];\n\t1213 -> 967 [penwidth=1, color=black];\n\t1213 -> 968 [penwidth=1, color=black];\n\t1213 -> 969 [penwidth=1, color=black];\n\t1213 -> 970 [penwidth=1, color=black];\n\t1213 -> 971 [penwidth=1, color=black];\n\t1213 -> 972 [penwidth=1, color=black];\n\t1213 -> 973 [penwidth=1, color=black];\n\t1213 -> 974 [penwidth=1, color=black];\n\t1213 -> 975 [penwidth=1, color=black];\n\t1213 -> 976 [penwidth=1, color=black];\n\t1213 -> 977 [penwidth=1, color=black];\n\t1213 -> 978 [penwidth=1, color=black];\n\t1213 -> 979 [penwidth=1, color=black];\n\t1213 -> 980 [penwidth=1, color=black];\n\t1213 -> 981 [penwidth=1, color=black];\n\t1213 -> 982 [penwidth=1, color=black];\n\t1213 -> 983 [penwidth=1, color=black];\n\t1213 -> 984 [penwidth=1, color=black];\n\t1213 -> 985 [penwidth=1, color=black];\n\t1213 -> 986 [penwidth=1, color=black];\n\t1213 -> 987 [penwidth=1, color=black];\n\t1213 -> 988 [penwidth=1, color=black];\n\t1213 -> 989 [penwidth=1, color=black];\n\t1213 -> 990 [penwidth=1, color=black];\n\t1213 -> 991 [penwidth=1, color=black];\n\t1213 -> 992 [penwidth=1, color=black];\n\t1213 -> 993 [penwidth=1, color=black];\n\t1213 -> 994 [penwidth=1, color=black];\n\t1213 -> 995 [penwidth=1, color=black];\n\t1213 -> 996 [penwidth=1, color=black];\n\t1213 -> 997 [penwidth=1, color=black];\n\t1213 -> 998 [penwidth=1, color=black];\n\t1213 -> 999 [penwidth=1, color=black];\n\t1213 -> 1000 [penwidth=1, color=black];\n\t1213 -> 1001 [penwidth=1, color=black];\n\t1213 -> 1002 [penwidth=1, color=black];\n\t1213 -> 1003 [penwidth=1, color=black];\n\t1213 -> 1004 [penwidth=1, color=black];\n\t1213 -> 1005 [penwidth=1, color=black];\n\t1213 -> 1006 [penwidth=1, color=black];\n\t1213 -> 1007 [penwidth=1, color=black];\n\t1213 -> 1008 [penwidth=1, color=black];\n\t1213 -> 1009 [penwidth=1, color=black];\n\t1213 -> 1010 [penwidth=1, color=black];\n\t1213 -> 1011 [penwidth=1, color=black];\n\t1213 -> 1012 [penwidth=1, color=black];\n\t1213 -> 1013 [penwidth=1, color=black];\n\t1213 -> 1014 [penwidth=1, color=black];\n\t1213 -> 1015 [penwidth=1, color=black];\n\t1213 -> 1016 [penwidth=1, color=black];\n\t1213 -> 1017 [penwidth=1, color=black];\n\t1213 -> 1019 [penwidth=1, color=black];\n\t1213 -> 1020 [penwidth=1, color=black];\n\t1213 -> 1021 [penwidth=1, color=black];\n\t1213 -> 1022 [penwidth=1, color=black];\n\t1213 -> 1023 [penwidth=1, color=black];\n\t1213 -> 1026 [penwidth=1, color=black];\n\t1213 -> 1027 [penwidth=1, color=black];\n\t1213 -> 1028 [penwidth=1, color=black];\n\t1213 -> 1029 [penwidth=1, color=black];\n\t1213 -> 1030 [penwidth=1, color=black];\n\t1213 -> 1031 [penwidth=1, color=black];\n\t1213 -> 1032 [penwidth=1, color=black];\n\t1213 -> 1033 [penwidth=1, color=black];\n\t1213 -> 1034 [penwidth=1, color=black];\n\t1213 -> 1035 [penwidth=1, color=black];\n\t1213 -> 1036 [penwidth=1, color=black];\n\t1213 -> 1037 [penwidth=1, color=black];\n\t1213 -> 1038 [penwidth=1, color=black];\n\t1213 -> 1039 [penwidth=1, color=black];\n\t1213 -> 1040 [penwidth=1, color=black];\n\t1213 -> 1041 [penwidth=1, color=black];\n\t1213 -> 1042 [penwidth=1, color=black];\n\t1213 -> 1045 [penwidth=1, color=black];\n\t1213 -> 1046 [penwidth=1, color=black];\n\t1213 -> 1047 [penwidth=1, color=black];\n\t1213 -> 1048 [penwidth=1, color=black];\n\t1213 -> 1049 [penwidth=1, color=black];\n\t1213 -> 1050 [penwidth=1, color=black];\n\t1213 -> 1051 [penwidth=1, color=black];\n\t1213 -> 1052 [penwidth=1, color=black];\n\t1213 -> 1053 [penwidth=1, color=black];\n\t1213 -> 1054 [penwidth=1, color=black];\n\t1213 -> 1055 [penwidth=1, color=black];\n\t1213 -> 1057 [penwidth=1, color=black];\n\t1213 -> 1058 [penwidth=1, color=black];\n\t1213 -> 1059 [penwidth=1, color=black];\n\t1213 -> 1060 [penwidth=1, color=black];\n\t1213 -> 1061 [penwidth=1, color=black];\n\t1213 -> 1062 [penwidth=1, color=black];\n\t1213 -> 1068 [penwidth=1, color=black];\n\t1213 -> 1069 [penwidth=1, color=black];\n\t1213 -> 1070 [penwidth=1, color=black];\n\t1213 -> 1071 [penwidth=1, color=black];\n\t1213 -> 1072 [penwidth=1, color=black];\n\t1213 -> 1081 [penwidth=1, color=black];\n\t1213 -> 1082 [penwidth=1, color=black];\n\t1213 -> 1083 [penwidth=1, color=black];\n\t1213 -> 1084 [penwidth=1, color=black];\n\t1213 -> 1085 [penwidth=1, color=black];\n\t1213 -> 1087 [penwidth=1, color=black];\n\t1213 -> 1088 [penwidth=1, color=black];\n\t1213 -> 1089 [penwidth=1, color=black];\n\t1213 -> 1090 [penwidth=1, color=black];\n\t1213 -> 1091 [penwidth=1, color=black];\n\t1213 -> 1092 [penwidth=1, color=black];\n\t1213 -> 1093 [penwidth=1, color=black];\n\t1213 -> 1094 [penwidth=1, color=black];\n\t1213 -> 1095 [penwidth=1, color=black];\n\t1213 -> 1096 [penwidth=1, color=black];\n\t1213 -> 1097 [penwidth=1, color=black];\n\t1213 -> 1098 [penwidth=1, color=black];\n\t1213 -> 1099 [penwidth=1, color=black];\n\t1213 -> 1100 [penwidth=1, color=black];\n\t1213 -> 1101 [penwidth=1, color=black];\n\t1213 -> 1102 [penwidth=1, color=black];\n\t1213 -> 1103 [penwidth=1, color=black];\n\t1213 -> 1104 [penwidth=1, color=black];\n\t1213 -> 1105 [penwidth=1, color=black];\n\t1213 -> 1106 [penwidth=1, color=black];\n\t1213 -> 1107 [penwidth=1, color=black];\n\t1213 -> 1108 [penwidth=1, color=black];\n\t1213 -> 1109 [penwidth=1, color=black];\n\t1213 -> 1110 [penwidth=1, color=black];\n\t1213 -> 1111 [penwidth=1, color=black];\n\t1213 -> 1112 [penwidth=1, color=black];\n\t1213 -> 1113 [penwidth=1, color=black];\n\t1213 -> 1117 [penwidth=1, color=black];\n\t1213 -> 1118 [penwidth=1, color=black];\n\t1213 -> 1119 [penwidth=1, color=black];\n\t1213 -> 1120 [penwidth=1, color=black];\n\t1213 -> 1121 [penwidth=1, color=black];\n\t1213 -> 1122 [penwidth=1, color=black];\n\t1213 -> 1123 [penwidth=1, color=black];\n\t1213 -> 1124 [penwidth=1, color=black];\n\t1213 -> 1125 [penwidth=1, color=black];\n\t1213 -> 1126 [penwidth=1, color=black];\n\t1213 -> 1127 [penwidth=1, color=black];\n\t1213 -> 1128 [penwidth=1, color=black];\n\t1213 -> 1129 [penwidth=1, color=black];\n\t1213 -> 1130 [penwidth=1, color=black];\n\t1213 -> 1131 [penwidth=1, color=black];\n\t1213 -> 1132 [penwidth=1, color=black];\n\t1213 -> 1133 [penwidth=1, color=black];\n\t1213 -> 1134 [penwidth=1, color=black];\n\t1213 -> 1135 [penwidth=1, color=black];\n\t1213 -> 1136 [penwidth=1, color=black];\n\t1213 -> 1137 [penwidth=1, color=black];\n\t1213 -> 1138 [penwidth=1, color=black];\n\t1213 -> 1139 [penwidth=1, color=black];\n\t1213 -> 1140 [penwidth=1, color=black];\n\t1213 -> 1141 [penwidth=1, color=black];\n\t1213 -> 1143 [penwidth=1, color=black];\n\t1213 -> 1144 [penwidth=1, color=black];\n\t1213 -> 1145 [penwidth=1, color=black];\n\t1213 -> 1146 [penwidth=1, color=black];\n\t1213 -> 1147 [penwidth=1, color=black];\n\t1213 -> 1148 [penwidth=1, color=black];\n\t1213 -> 1149 [penwidth=1, color=black];\n\t1213 -> 1150 [penwidth=1, color=black];\n\t1213 -> 1151 [penwidth=1, color=black];\n\t1213 -> 1152 [penwidth=1, color=black];\n\t1213 -> 1153 [penwidth=1, color=black];\n\t1213 -> 1154 [penwidth=1, color=black];\n\t1213 -> 1155 [penwidth=1, color=black];\n\t1213 -> 1156 [penwidth=1, color=black];\n\t1213 -> 1157 [penwidth=1, color=black];\n\t1213 -> 1158 [penwidth=1, color=black];\n\t1213 -> 1159 [penwidth=1, color=black];\n\t1213 -> 1160 [penwidth=1, color=black];\n\t1213 -> 1161 [penwidth=1, color=black];\n\t1213 -> 1162 [penwidth=1, color=black];\n\t1213 -> 1163 [penwidth=1, color=black];\n\t1213 -> 1164 [penwidth=1, color=black];\n\t1213 -> 1165 [penwidth=1, color=black];\n\t1213 -> 1166 [penwidth=1, color=black];\n\t1213 -> 1167 [penwidth=1, color=black];\n\t1213 -> 1168 [penwidth=1, color=black];\n\t1213 -> 1169 [penwidth=1, color=black];\n\t1213 -> 1170 [penwidth=1, color=black];\n\t1213 -> 1171 [penwidth=1, color=black];\n\t1213 -> 1172 [penwidth=1, color=black];\n\t1213 -> 1173 [penwidth=1, color=black];\n\t1213 -> 1174 [penwidth=1, color=black];\n\t1213 -> 1175 [penwidth=1, color=black];\n\t1213 -> 1176 [penwidth=1, color=black];\n\t1213 -> 1177 [penwidth=1, color=black];\n\t1213 -> 1178 [penwidth=1, color=black];\n\t1213 -> 1179 [penwidth=1, color=black];\n\t1213 -> 1180 [penwidth=1, color=black];\n\t1213 -> 1181 [penwidth=1, color=black];\n\t1213 -> 1182 [penwidth=1, color=black];\n\t1213 -> 1183 [penwidth=1, color=black];\n\t1213 -> 1184 [penwidth=1, color=black];\n\t1213 -> 1185 [penwidth=1, color=black];\n\t1213 -> 1186 [penwidth=1, color=black];\n\t1213 -> 1189 [penwidth=1, color=black];\n\t1213 -> 1190 [penwidth=1, color=black];\n\t1213 -> 1191 [penwidth=1, color=black];\n\t1213 -> 1192 [penwidth=1, color=black];\n\t1213 -> 1193 [penwidth=1, color=black];\n\t1213 -> 1194 [penwidth=1, color=black];\n\t1213 -> 1435 [penwidth=\"7.063785208687608\", color=black];\n\t1213 -> 1436 [penwidth=\"5.7535901911063645\", color=black];\n\t1214 -> 1373 [penwidth=1, color=black];\n\t1217 -> 644 [penwidth=1, color=black];\n\t1217 -> 873 [penwidth=1, color=black];\n\t1217 -> 1074 [penwidth=1, color=black];\n\t1217 -> 1075 [penwidth=1, color=black];\n\t1217 -> 1188 [penwidth=1, color=black];\n\t1217 -> 1219 [penwidth=1, color=black];\n\t1217 -> 1227 [penwidth=1, color=black];\n\t1218 -> 644 [penwidth=1, color=black];\n\t1218 -> 1188 [penwidth=1, color=black];\n\t1219 -> 1207 [penwidth=1, color=black];\n\t1220 -> 611 [penwidth=1, color=black];\n\t1220 -> 642 [penwidth=1, color=black];\n\t1220 -> 643 [penwidth=1, color=black];\n\t1220 -> 651 [penwidth=1, color=black];\n\t1220 -> 652 [penwidth=1, color=black];\n\t1220 -> 690 [penwidth=1, color=black];\n\t1220 -> 752 [penwidth=1, color=black];\n\t1220 -> 871 [penwidth=1, color=black];\n\t1220 -> 872 [penwidth=1, color=black];\n\t1220 -> 1018 [penwidth=1, color=black];\n\t1220 -> 1024 [penwidth=1, color=black];\n\t1220 -> 1025 [penwidth=1, color=black];\n\t1220 -> 1043 [penwidth=1, color=black];\n\t1220 -> 1044 [penwidth=1, color=black];\n\t1220 -> 1056 [penwidth=1, color=black];\n\t1220 -> 1063 [penwidth=1, color=black];\n\t1220 -> 1064 [penwidth=1, color=black];\n\t1220 -> 1065 [penwidth=1, color=black];\n\t1220 -> 1066 [penwidth=1, color=black];\n\t1220 -> 1067 [penwidth=1, color=black];\n\t1220 -> 1073 [penwidth=1, color=black];\n\t1220 -> 1076 [penwidth=1, color=black];\n\t1220 -> 1077 [penwidth=1, color=black];\n\t1220 -> 1078 [penwidth=1, color=black];\n\t1220 -> 1079 [penwidth=1, color=black];\n\t1220 -> 1080 [penwidth=1, color=black];\n\t1220 -> 1086 [penwidth=1, color=black];\n\t1220 -> 1114 [penwidth=1, color=black];\n\t1220 -> 1115 [penwidth=1, color=black];\n\t1220 -> 1116 [penwidth=1, color=black];\n\t1220 -> 1142 [penwidth=1, color=black];\n\t1220 -> 1195 [penwidth=1, color=black];\n\t1220 -> 1196 [penwidth=1, color=black];\n\t1220 -> 1197 [penwidth=1, color=black];\n\t1220 -> 1198 [penwidth=1, color=black];\n\t1221 -> 644 [penwidth=1, color=black];\n\t1221 -> 873 [penwidth=1, color=black];\n\t1221 -> 1074 [penwidth=1, color=black];\n\t1221 -> 1075 [penwidth=1, color=black];\n\t1221 -> 1188 [penwidth=1, color=black];\n\t1221 -> 1204 [penwidth=\"1.6931471805599454\", color=black];\n\t1222 -> 645 [penwidth=1, color=black];\n\t1222 -> 1187 [penwidth=1, color=black];\n\t1223 -> 612 [penwidth=1, color=black];\n\t1223 -> 613 [penwidth=1, color=black];\n\t1223 -> 614 [penwidth=1, color=black];\n\t1223 -> 615 [penwidth=1, color=black];\n\t1223 -> 616 [penwidth=1, color=black];\n\t1223 -> 617 [penwidth=1, color=black];\n\t1223 -> 618 [penwidth=1, color=black];\n\t1223 -> 619 [penwidth=1, color=black];\n\t1223 -> 620 [penwidth=1, color=black];\n\t1223 -> 621 [penwidth=1, color=black];\n\t1223 -> 622 [penwidth=1, color=black];\n\t1223 -> 623 [penwidth=1, color=black];\n\t1223 -> 624 [penwidth=1, color=black];\n\t1223 -> 625 [penwidth=1, color=black];\n\t1223 -> 626 [penwidth=1, color=black];\n\t1223 -> 627 [penwidth=1, color=black];\n\t1223 -> 628 [penwidth=1, color=black];\n\t1223 -> 629 [penwidth=1, color=black];\n\t1223 -> 630 [penwidth=1, color=black];\n\t1223 -> 631 [penwidth=1, color=black];\n\t1223 -> 632 [penwidth=1, color=black];\n\t1223 -> 633 [penwidth=1, color=black];\n\t1223 -> 634 [penwidth=1, color=black];\n\t1223 -> 635 [penwidth=1, color=black];\n\t1223 -> 636 [penwidth=1, color=black];\n\t1223 -> 637 [penwidth=1, color=black];\n\t1223 -> 638 [penwidth=1, color=black];\n\t1223 -> 639 [penwidth=1, color=black];\n\t1223 -> 640 [penwidth=1, color=black];\n\t1223 -> 641 [penwidth=1, color=black];\n\t1223 -> 646 [penwidth=1, color=black];\n\t1223 -> 647 [penwidth=1, color=black];\n\t1223 -> 648 [penwidth=1, color=black];\n\t1223 -> 649 [penwidth=1, color=black];\n\t1223 -> 650 [penwidth=1, color=black];\n\t1223 -> 653 [penwidth=1, color=black];\n\t1223 -> 654 [penwidth=1, color=black];\n\t1223 -> 655 [penwidth=1, color=black];\n\t1223 -> 656 [penwidth=1, color=black];\n\t1223 -> 657 [penwidth=1, color=black];\n\t1223 -> 658 [penwidth=1, color=black];\n\t1223 -> 659 [penwidth=1, color=black];\n\t1223 -> 660 [penwidth=1, color=black];\n\t1223 -> 661 [penwidth=1, color=black];\n\t1223 -> 662 [penwidth=1, color=black];\n\t1223 -> 663 [penwidth=1, color=black];\n\t1223 -> 664 [penwidth=1, color=black];\n\t1223 -> 665 [penwidth=1, color=black];\n\t1223 -> 666 [penwidth=1, color=black];\n\t1223 -> 667 [penwidth=1, color=black];\n\t1223 -> 668 [penwidth=1, color=black];\n\t1223 -> 669 [penwidth=1, color=black];\n\t1223 -> 670 [penwidth=1, color=black];\n\t1223 -> 671 [penwidth=1, color=black];\n\t1223 -> 672 [penwidth=1, color=black];\n\t1223 -> 673 [penwidth=1, color=black];\n\t1223 -> 674 [penwidth=1, color=black];\n\t1223 -> 675 [penwidth=1, color=black];\n\t1223 -> 676 [penwidth=1, color=black];\n\t1223 -> 677 [penwidth=1, color=black];\n\t1223 -> 678 [penwidth=1, color=black];\n\t1223 -> 679 [penwidth=1, color=black];\n\t1223 -> 680 [penwidth=1, color=black];\n\t1223 -> 681 [penwidth=1, color=black];\n\t1223 -> 682 [penwidth=1, color=black];\n\t1223 -> 683 [penwidth=1, color=black];\n\t1223 -> 684 [penwidth=1, color=black];\n\t1223 -> 685 [penwidth=1, color=black];\n\t1223 -> 686 [penwidth=1, color=black];\n\t1223 -> 687 [penwidth=1, color=black];\n\t1223 -> 688 [penwidth=1, color=black];\n\t1223 -> 689 [penwidth=1, color=black];\n\t1223 -> 691 [penwidth=1, color=black];\n\t1223 -> 692 [penwidth=1, color=black];\n\t1223 -> 693 [penwidth=1, color=black];\n\t1223 -> 694 [penwidth=1, color=black];\n\t1223 -> 695 [penwidth=1, color=black];\n\t1223 -> 696 [penwidth=1, color=black];\n\t1223 -> 697 [penwidth=1, color=black];\n\t1223 -> 698 [penwidth=1, color=black];\n\t1223 -> 699 [penwidth=1, color=black];\n\t1223 -> 700 [penwidth=1, color=black];\n\t1223 -> 701 [penwidth=1, color=black];\n\t1223 -> 702 [penwidth=1, color=black];\n\t1223 -> 703 [penwidth=1, color=black];\n\t1223 -> 704 [penwidth=1, color=black];\n\t1223 -> 705 [penwidth=1, color=black];\n\t1223 -> 706 [penwidth=1, color=black];\n\t1223 -> 707 [penwidth=1, color=black];\n\t1223 -> 708 [penwidth=1, color=black];\n\t1223 -> 709 [penwidth=1, color=black];\n\t1223 -> 710 [penwidth=1, color=black];\n\t1223 -> 711 [penwidth=1, color=black];\n\t1223 -> 712 [penwidth=1, color=black];\n\t1223 -> 713 [penwidth=1, color=black];\n\t1223 -> 714 [penwidth=1, color=black];\n\t1223 -> 715 [penwidth=1, color=black];\n\t1223 -> 716 [penwidth=1, color=black];\n\t1223 -> 717 [penwidth=1, color=black];\n\t1223 -> 718 [penwidth=1, color=black];\n\t1223 -> 719 [penwidth=1, color=black];\n\t1223 -> 720 [penwidth=1, color=black];\n\t1223 -> 721 [penwidth=1, color=black];\n\t1223 -> 722 [penwidth=1, color=black];\n\t1223 -> 723 [penwidth=1, color=black];\n\t1223 -> 724 [penwidth=1, color=black];\n\t1223 -> 725 [penwidth=1, color=black];\n\t1223 -> 726 [penwidth=1, color=black];\n\t1223 -> 727 [penwidth=1, color=black];\n\t1223 -> 728 [penwidth=1, color=black];\n\t1223 -> 729 [penwidth=1, color=black];\n\t1223 -> 730 [penwidth=1, color=black];\n\t1223 -> 731 [penwidth=1, color=black];\n\t1223 -> 732 [penwidth=1, color=black];\n\t1223 -> 733 [penwidth=1, color=black];\n\t1223 -> 734 [penwidth=1, color=black];\n\t1223 -> 735 [penwidth=1, color=black];\n\t1223 -> 736 [penwidth=1, color=black];\n\t1223 -> 737 [penwidth=1, color=black];\n\t1223 -> 738 [penwidth=1, color=black];\n\t1223 -> 739 [penwidth=1, color=black];\n\t1223 -> 740 [penwidth=1, color=black];\n\t1223 -> 741 [penwidth=1, color=black];\n\t1223 -> 742 [penwidth=1, color=black];\n\t1223 -> 743 [penwidth=1, color=black];\n\t1223 -> 744 [penwidth=1, color=black];\n\t1223 -> 745 [penwidth=1, color=black];\n\t1223 -> 746 [penwidth=1, color=black];\n\t1223 -> 747 [penwidth=1, color=black];\n\t1223 -> 748 [penwidth=1, color=black];\n\t1223 -> 749 [penwidth=1, color=black];\n\t1223 -> 750 [penwidth=1, color=black];\n\t1223 -> 751 [penwidth=1, color=black];\n\t1223 -> 753 [penwidth=1, color=black];\n\t1223 -> 754 [penwidth=1, color=black];\n\t1223 -> 755 [penwidth=1, color=black];\n\t1223 -> 756 [penwidth=1, color=black];\n\t1223 -> 757 [penwidth=1, color=black];\n\t1223 -> 758 [penwidth=1, color=black];\n\t1223 -> 759 [penwidth=1, color=black];\n\t1223 -> 760 [penwidth=1, color=black];\n\t1223 -> 761 [penwidth=1, color=black];\n\t1223 -> 762 [penwidth=1, color=black];\n\t1223 -> 763 [penwidth=1, color=black];\n\t1223 -> 764 [penwidth=1, color=black];\n\t1223 -> 765 [penwidth=1, color=black];\n\t1223 -> 766 [penwidth=1, color=black];\n\t1223 -> 767 [penwidth=1, color=black];\n\t1223 -> 768 [penwidth=1, color=black];\n\t1223 -> 769 [penwidth=1, color=black];\n\t1223 -> 770 [penwidth=1, color=black];\n\t1223 -> 771 [penwidth=1, color=black];\n\t1223 -> 772 [penwidth=1, color=black];\n\t1223 -> 773 [penwidth=1, color=black];\n\t1223 -> 774 [penwidth=1, color=black];\n\t1223 -> 775 [penwidth=1, color=black];\n\t1223 -> 776 [penwidth=1, color=black];\n\t1223 -> 777 [penwidth=1, color=black];\n\t1223 -> 778 [penwidth=1, color=black];\n\t1223 -> 779 [penwidth=1, color=black];\n\t1223 -> 780 [penwidth=1, color=black];\n\t1223 -> 781 [penwidth=1, color=black];\n\t1223 -> 782 [penwidth=1, color=black];\n\t1223 -> 783 [penwidth=1, color=black];\n\t1223 -> 784 [penwidth=1, color=black];\n\t1223 -> 785 [penwidth=1, color=black];\n\t1223 -> 786 [penwidth=1, color=black];\n\t1223 -> 787 [penwidth=1, color=black];\n\t1223 -> 788 [penwidth=1, color=black];\n\t1223 -> 789 [penwidth=1, color=black];\n\t1223 -> 790 [penwidth=1, color=black];\n\t1223 -> 791 [penwidth=1, color=black];\n\t1223 -> 792 [penwidth=1, color=black];\n\t1223 -> 793 [penwidth=1, color=black];\n\t1223 -> 794 [penwidth=1, color=black];\n\t1223 -> 795 [penwidth=1, color=black];\n\t1223 -> 796 [penwidth=1, color=black];\n\t1223 -> 797 [penwidth=1, color=black];\n\t1223 -> 798 [penwidth=1, color=black];\n\t1223 -> 799 [penwidth=1, color=black];\n\t1223 -> 800 [penwidth=1, color=black];\n\t1223 -> 801 [penwidth=1, color=black];\n\t1223 -> 802 [penwidth=1, color=black];\n\t1223 -> 803 [penwidth=1, color=black];\n\t1223 -> 804 [penwidth=1, color=black];\n\t1223 -> 805 [penwidth=1, color=black];\n\t1223 -> 806 [penwidth=1, color=black];\n\t1223 -> 807 [penwidth=1, color=black];\n\t1223 -> 808 [penwidth=1, color=black];\n\t1223 -> 809 [penwidth=1, color=black];\n\t1223 -> 810 [penwidth=1, color=black];\n\t1223 -> 811 [penwidth=1, color=black];\n\t1223 -> 812 [penwidth=1, color=black];\n\t1223 -> 813 [penwidth=1, color=black];\n\t1223 -> 814 [penwidth=1, color=black];\n\t1223 -> 815 [penwidth=1, color=black];\n\t1223 -> 816 [penwidth=1, color=black];\n\t1223 -> 817 [penwidth=1, color=black];\n\t1223 -> 818 [penwidth=1, color=black];\n\t1223 -> 819 [penwidth=1, color=black];\n\t1223 -> 820 [penwidth=1, color=black];\n\t1223 -> 821 [penwidth=1, color=black];\n\t1223 -> 822 [penwidth=1, color=black];\n\t1223 -> 823 [penwidth=1, color=black];\n\t1223 -> 824 [penwidth=1, color=black];\n\t1223 -> 825 [penwidth=1, color=black];\n\t1223 -> 826 [penwidth=1, color=black];\n\t1223 -> 827 [penwidth=1, color=black];\n\t1223 -> 828 [penwidth=1, color=black];\n\t1223 -> 829 [penwidth=1, color=black];\n\t1223 -> 830 [penwidth=1, color=black];\n\t1223 -> 831 [penwidth=1, color=black];\n\t1223 -> 832 [penwidth=1, color=black];\n\t1223 -> 833 [penwidth=1, color=black];\n\t1223 -> 834 [penwidth=1, color=black];\n\t1223 -> 835 [penwidth=1, color=black];\n\t1223 -> 836 [penwidth=1, color=black];\n\t1223 -> 837 [penwidth=1, color=black];\n\t1223 -> 838 [penwidth=1, color=black];\n\t1223 -> 839 [penwidth=1, color=black];\n\t1223 -> 840 [penwidth=1, color=black];\n\t1223 -> 841 [penwidth=1, color=black];\n\t1223 -> 842 [penwidth=1, color=black];\n\t1223 -> 843 [penwidth=1, color=black];\n\t1223 -> 844 [penwidth=1, color=black];\n\t1223 -> 845 [penwidth=1, color=black];\n\t1223 -> 846 [penwidth=1, color=black];\n\t1223 -> 847 [penwidth=1, color=black];\n\t1223 -> 848 [penwidth=1, color=black];\n\t1223 -> 849 [penwidth=1, color=black];\n\t1223 -> 850 [penwidth=1, color=black];\n\t1223 -> 851 [penwidth=1, color=black];\n\t1223 -> 852 [penwidth=1, color=black];\n\t1223 -> 853 [penwidth=1, color=black];\n\t1223 -> 854 [penwidth=1, color=black];\n\t1223 -> 855 [penwidth=1, color=black];\n\t1223 -> 856 [penwidth=1, color=black];\n\t1223 -> 857 [penwidth=1, color=black];\n\t1223 -> 858 [penwidth=1, color=black];\n\t1223 -> 859 [penwidth=1, color=black];\n\t1223 -> 860 [penwidth=1, color=black];\n\t1223 -> 861 [penwidth=1, color=black];\n\t1223 -> 862 [penwidth=1, color=black];\n\t1223 -> 863 [penwidth=1, color=black];\n\t1223 -> 864 [penwidth=1, color=black];\n\t1223 -> 865 [penwidth=1, color=black];\n\t1223 -> 866 [penwidth=1, color=black];\n\t1223 -> 867 [penwidth=1, color=black];\n\t1223 -> 868 [penwidth=1, color=black];\n\t1223 -> 869 [penwidth=1, color=black];\n\t1223 -> 870 [penwidth=1, color=black];\n\t1223 -> 874 [penwidth=1, color=black];\n\t1223 -> 875 [penwidth=1, color=black];\n\t1223 -> 876 [penwidth=1, color=black];\n\t1223 -> 877 [penwidth=1, color=black];\n\t1223 -> 878 [penwidth=1, color=black];\n\t1223 -> 879 [penwidth=1, color=black];\n\t1223 -> 880 [penwidth=1, color=black];\n\t1223 -> 881 [penwidth=1, color=black];\n\t1223 -> 882 [penwidth=1, color=black];\n\t1223 -> 883 [penwidth=1, color=black];\n\t1223 -> 884 [penwidth=1, color=black];\n\t1223 -> 885 [penwidth=1, color=black];\n\t1223 -> 886 [penwidth=1, color=black];\n\t1223 -> 887 [penwidth=1, color=black];\n\t1223 -> 888 [penwidth=1, color=black];\n\t1223 -> 889 [penwidth=1, color=black];\n\t1223 -> 890 [penwidth=1, color=black];\n\t1223 -> 891 [penwidth=1, color=black];\n\t1223 -> 892 [penwidth=1, color=black];\n\t1223 -> 893 [penwidth=1, color=black];\n\t1223 -> 894 [penwidth=1, color=black];\n\t1223 -> 895 [penwidth=1, color=black];\n\t1223 -> 896 [penwidth=1, color=black];\n\t1223 -> 897 [penwidth=1, color=black];\n\t1223 -> 898 [penwidth=1, color=black];\n\t1223 -> 899 [penwidth=1, color=black];\n\t1223 -> 900 [penwidth=1, color=black];\n\t1223 -> 901 [penwidth=1, color=black];\n\t1223 -> 902 [penwidth=1, color=black];\n\t1223 -> 903 [penwidth=1, color=black];\n\t1223 -> 904 [penwidth=1, color=black];\n\t1223 -> 905 [penwidth=1, color=black];\n\t1223 -> 906 [penwidth=1, color=black];\n\t1223 -> 907 [penwidth=1, color=black];\n\t1223 -> 908 [penwidth=1, color=black];\n\t1223 -> 909 [penwidth=1, color=black];\n\t1223 -> 910 [penwidth=1, color=black];\n\t1223 -> 911 [penwidth=1, color=black];\n\t1223 -> 912 [penwidth=1, color=black];\n\t1223 -> 913 [penwidth=1, color=black];\n\t1223 -> 914 [penwidth=1, color=black];\n\t1223 -> 915 [penwidth=1, color=black];\n\t1223 -> 916 [penwidth=1, color=black];\n\t1223 -> 917 [penwidth=1, color=black];\n\t1223 -> 918 [penwidth=1, color=black];\n\t1223 -> 919 [penwidth=1, color=black];\n\t1223 -> 920 [penwidth=1, color=black];\n\t1223 -> 921 [penwidth=1, color=black];\n\t1223 -> 922 [penwidth=1, color=black];\n\t1223 -> 923 [penwidth=1, color=black];\n\t1223 -> 924 [penwidth=1, color=black];\n\t1223 -> 925 [penwidth=1, color=black];\n\t1223 -> 926 [penwidth=1, color=black];\n\t1223 -> 927 [penwidth=1, color=black];\n\t1223 -> 928 [penwidth=1, color=black];\n\t1223 -> 929 [penwidth=1, color=black];\n\t1223 -> 930 [penwidth=1, color=black];\n\t1223 -> 931 [penwidth=1, color=black];\n\t1223 -> 932 [penwidth=1, color=black];\n\t1223 -> 933 [penwidth=1, color=black];\n\t1223 -> 934 [penwidth=1, color=black];\n\t1223 -> 935 [penwidth=1, color=black];\n\t1223 -> 936 [penwidth=1, color=black];\n\t1223 -> 937 [penwidth=1, color=black];\n\t1223 -> 938 [penwidth=1, color=black];\n\t1223 -> 939 [penwidth=1, color=black];\n\t1223 -> 940 [penwidth=1, color=black];\n\t1223 -> 941 [penwidth=1, color=black];\n\t1223 -> 942 [penwidth=1, color=black];\n\t1223 -> 943 [penwidth=1, color=black];\n\t1223 -> 944 [penwidth=1, color=black];\n\t1223 -> 945 [penwidth=1, color=black];\n\t1223 -> 946 [penwidth=1, color=black];\n\t1223 -> 947 [penwidth=1, color=black];\n\t1223 -> 948 [penwidth=1, color=black];\n\t1223 -> 949 [penwidth=1, color=black];\n\t1223 -> 950 [penwidth=1, color=black];\n\t1223 -> 951 [penwidth=1, color=black];\n\t1223 -> 952 [penwidth=1, color=black];\n\t1223 -> 953 [penwidth=1, color=black];\n\t1223 -> 954 [penwidth=1, color=black];\n\t1223 -> 955 [penwidth=1, color=black];\n\t1223 -> 956 [penwidth=1, color=black];\n\t1223 -> 957 [penwidth=1, color=black];\n\t1223 -> 958 [penwidth=1, color=black];\n\t1223 -> 959 [penwidth=1, color=black];\n\t1223 -> 960 [penwidth=1, color=black];\n\t1223 -> 961 [penwidth=1, color=black];\n\t1223 -> 962 [penwidth=1, color=black];\n\t1223 -> 963 [penwidth=1, color=black];\n\t1223 -> 964 [penwidth=1, color=black];\n\t1223 -> 965 [penwidth=1, color=black];\n\t1223 -> 966 [penwidth=1, color=black];\n\t1223 -> 967 [penwidth=1, color=black];\n\t1223 -> 968 [penwidth=1, color=black];\n\t1223 -> 969 [penwidth=1, color=black];\n\t1223 -> 970 [penwidth=1, color=black];\n\t1223 -> 971 [penwidth=1, color=black];\n\t1223 -> 972 [penwidth=1, color=black];\n\t1223 -> 973 [penwidth=1, color=black];\n\t1223 -> 974 [penwidth=1, color=black];\n\t1223 -> 975 [penwidth=1, color=black];\n\t1223 -> 976 [penwidth=1, color=black];\n\t1223 -> 977 [penwidth=1, color=black];\n\t1223 -> 978 [penwidth=1, color=black];\n\t1223 -> 979 [penwidth=1, color=black];\n\t1223 -> 980 [penwidth=1, color=black];\n\t1223 -> 981 [penwidth=1, color=black];\n\t1223 -> 982 [penwidth=1, color=black];\n\t1223 -> 983 [penwidth=1, color=black];\n\t1223 -> 984 [penwidth=1, color=black];\n\t1223 -> 985 [penwidth=1, color=black];\n\t1223 -> 986 [penwidth=1, color=black];\n\t1223 -> 987 [penwidth=1, color=black];\n\t1223 -> 988 [penwidth=1, color=black];\n\t1223 -> 989 [penwidth=1, color=black];\n\t1223 -> 990 [penwidth=1, color=black];\n\t1223 -> 991 [penwidth=1, color=black];\n\t1223 -> 992 [penwidth=1, color=black];\n\t1223 -> 993 [penwidth=1, color=black];\n\t1223 -> 994 [penwidth=1, color=black];\n\t1223 -> 995 [penwidth=1, color=black];\n\t1223 -> 996 [penwidth=1, color=black];\n\t1223 -> 997 [penwidth=1, color=black];\n\t1223 -> 998 [penwidth=1, color=black];\n\t1223 -> 999 [penwidth=1, color=black];\n\t1223 -> 1000 [penwidth=1, color=black];\n\t1223 -> 1001 [penwidth=1, color=black];\n\t1223 -> 1002 [penwidth=1, color=black];\n\t1223 -> 1003 [penwidth=1, color=black];\n\t1223 -> 1004 [penwidth=1, color=black];\n\t1223 -> 1005 [penwidth=1, color=black];\n\t1223 -> 1006 [penwidth=1, color=black];\n\t1223 -> 1007 [penwidth=1, color=black];\n\t1223 -> 1008 [penwidth=1, color=black];\n\t1223 -> 1009 [penwidth=1, color=black];\n\t1223 -> 1010 [penwidth=1, color=black];\n\t1223 -> 1011 [penwidth=1, color=black];\n\t1223 -> 1012 [penwidth=1, color=black];\n\t1223 -> 1013 [penwidth=1, color=black];\n\t1223 -> 1014 [penwidth=1, color=black];\n\t1223 -> 1015 [penwidth=1, color=black];\n\t1223 -> 1016 [penwidth=1, color=black];\n\t1223 -> 1017 [penwidth=1, color=black];\n\t1223 -> 1019 [penwidth=1, color=black];\n\t1223 -> 1020 [penwidth=1, color=black];\n\t1223 -> 1021 [penwidth=1, color=black];\n\t1223 -> 1022 [penwidth=1, color=black];\n\t1223 -> 1023 [penwidth=1, color=black];\n\t1223 -> 1026 [penwidth=1, color=black];\n\t1223 -> 1027 [penwidth=1, color=black];\n\t1223 -> 1028 [penwidth=1, color=black];\n\t1223 -> 1029 [penwidth=1, color=black];\n\t1223 -> 1030 [penwidth=1, color=black];\n\t1223 -> 1031 [penwidth=1, color=black];\n\t1223 -> 1032 [penwidth=1, color=black];\n\t1223 -> 1033 [penwidth=1, color=black];\n\t1223 -> 1034 [penwidth=1, color=black];\n\t1223 -> 1035 [penwidth=1, color=black];\n\t1223 -> 1036 [penwidth=1, color=black];\n\t1223 -> 1037 [penwidth=1, color=black];\n\t1223 -> 1038 [penwidth=1, color=black];\n\t1223 -> 1039 [penwidth=1, color=black];\n\t1223 -> 1040 [penwidth=1, color=black];\n\t1223 -> 1041 [penwidth=1, color=black];\n\t1223 -> 1042 [penwidth=1, color=black];\n\t1223 -> 1045 [penwidth=1, color=black];\n\t1223 -> 1046 [penwidth=1, color=black];\n\t1223 -> 1047 [penwidth=1, color=black];\n\t1223 -> 1048 [penwidth=1, color=black];\n\t1223 -> 1049 [penwidth=1, color=black];\n\t1223 -> 1050 [penwidth=1, color=black];\n\t1223 -> 1051 [penwidth=1, color=black];\n\t1223 -> 1052 [penwidth=1, color=black];\n\t1223 -> 1053 [penwidth=1, color=black];\n\t1223 -> 1054 [penwidth=1, color=black];\n\t1223 -> 1055 [penwidth=1, color=black];\n\t1223 -> 1057 [penwidth=1, color=black];\n\t1223 -> 1058 [penwidth=1, color=black];\n\t1223 -> 1059 [penwidth=1, color=black];\n\t1223 -> 1060 [penwidth=1, color=black];\n\t1223 -> 1061 [penwidth=1, color=black];\n\t1223 -> 1062 [penwidth=1, color=black];\n\t1223 -> 1068 [penwidth=1, color=black];\n\t1223 -> 1069 [penwidth=1, color=black];\n\t1223 -> 1070 [penwidth=1, color=black];\n\t1223 -> 1071 [penwidth=1, color=black];\n\t1223 -> 1072 [penwidth=1, color=black];\n\t1223 -> 1081 [penwidth=1, color=black];\n\t1223 -> 1082 [penwidth=1, color=black];\n\t1223 -> 1083 [penwidth=1, color=black];\n\t1223 -> 1084 [penwidth=1, color=black];\n\t1223 -> 1085 [penwidth=1, color=black];\n\t1223 -> 1087 [penwidth=1, color=black];\n\t1223 -> 1088 [penwidth=1, color=black];\n\t1223 -> 1089 [penwidth=1, color=black];\n\t1223 -> 1090 [penwidth=1, color=black];\n\t1223 -> 1091 [penwidth=1, color=black];\n\t1223 -> 1092 [penwidth=1, color=black];\n\t1223 -> 1093 [penwidth=1, color=black];\n\t1223 -> 1094 [penwidth=1, color=black];\n\t1223 -> 1095 [penwidth=1, color=black];\n\t1223 -> 1096 [penwidth=1, color=black];\n\t1223 -> 1097 [penwidth=1, color=black];\n\t1223 -> 1098 [penwidth=1, color=black];\n\t1223 -> 1099 [penwidth=1, color=black];\n\t1223 -> 1100 [penwidth=1, color=black];\n\t1223 -> 1101 [penwidth=1, color=black];\n\t1223 -> 1102 [penwidth=1, color=black];\n\t1223 -> 1103 [penwidth=1, color=black];\n\t1223 -> 1104 [penwidth=1, color=black];\n\t1223 -> 1105 [penwidth=1, color=black];\n\t1223 -> 1106 [penwidth=1, color=black];\n\t1223 -> 1107 [penwidth=1, color=black];\n\t1223 -> 1108 [penwidth=1, color=black];\n\t1223 -> 1109 [penwidth=1, color=black];\n\t1223 -> 1110 [penwidth=1, color=black];\n\t1223 -> 1111 [penwidth=1, color=black];\n\t1223 -> 1112 [penwidth=1, color=black];\n\t1223 -> 1113 [penwidth=1, color=black];\n\t1223 -> 1117 [penwidth=1, color=black];\n\t1223 -> 1118 [penwidth=1, color=black];\n\t1223 -> 1119 [penwidth=1, color=black];\n\t1223 -> 1120 [penwidth=1, color=black];\n\t1223 -> 1121 [penwidth=1, color=black];\n\t1223 -> 1122 [penwidth=1, color=black];\n\t1223 -> 1123 [penwidth=1, color=black];\n\t1223 -> 1124 [penwidth=1, color=black];\n\t1223 -> 1125 [penwidth=1, color=black];\n\t1223 -> 1126 [penwidth=1, color=black];\n\t1223 -> 1127 [penwidth=1, color=black];\n\t1223 -> 1128 [penwidth=1, color=black];\n\t1223 -> 1129 [penwidth=1, color=black];\n\t1223 -> 1130 [penwidth=1, color=black];\n\t1223 -> 1131 [penwidth=1, color=black];\n\t1223 -> 1132 [penwidth=1, color=black];\n\t1223 -> 1133 [penwidth=1, color=black];\n\t1223 -> 1134 [penwidth=1, color=black];\n\t1223 -> 1135 [penwidth=1, color=black];\n\t1223 -> 1136 [penwidth=1, color=black];\n\t1223 -> 1137 [penwidth=1, color=black];\n\t1223 -> 1138 [penwidth=1, color=black];\n\t1223 -> 1139 [penwidth=1, color=black];\n\t1223 -> 1140 [penwidth=1, color=black];\n\t1223 -> 1141 [penwidth=1, color=black];\n\t1223 -> 1143 [penwidth=1, color=black];\n\t1223 -> 1144 [penwidth=1, color=black];\n\t1223 -> 1145 [penwidth=1, color=black];\n\t1223 -> 1146 [penwidth=1, color=black];\n\t1223 -> 1147 [penwidth=1, color=black];\n\t1223 -> 1148 [penwidth=1, color=black];\n\t1223 -> 1149 [penwidth=1, color=black];\n\t1223 -> 1150 [penwidth=1, color=black];\n\t1223 -> 1151 [penwidth=1, color=black];\n\t1223 -> 1152 [penwidth=1, color=black];\n\t1223 -> 1153 [penwidth=1, color=black];\n\t1223 -> 1154 [penwidth=1, color=black];\n\t1223 -> 1155 [penwidth=1, color=black];\n\t1223 -> 1156 [penwidth=1, color=black];\n\t1223 -> 1157 [penwidth=1, color=black];\n\t1223 -> 1158 [penwidth=1, color=black];\n\t1223 -> 1159 [penwidth=1, color=black];\n\t1223 -> 1160 [penwidth=1, color=black];\n\t1223 -> 1161 [penwidth=1, color=black];\n\t1223 -> 1162 [penwidth=1, color=black];\n\t1223 -> 1163 [penwidth=1, color=black];\n\t1223 -> 1164 [penwidth=1, color=black];\n\t1223 -> 1165 [penwidth=1, color=black];\n\t1223 -> 1166 [penwidth=1, color=black];\n\t1223 -> 1167 [penwidth=1, color=black];\n\t1223 -> 1168 [penwidth=1, color=black];\n\t1223 -> 1169 [penwidth=1, color=black];\n\t1223 -> 1170 [penwidth=1, color=black];\n\t1223 -> 1171 [penwidth=1, color=black];\n\t1223 -> 1172 [penwidth=1, color=black];\n\t1223 -> 1173 [penwidth=1, color=black];\n\t1223 -> 1174 [penwidth=1, color=black];\n\t1223 -> 1175 [penwidth=1, color=black];\n\t1223 -> 1176 [penwidth=1, color=black];\n\t1223 -> 1177 [penwidth=1, color=black];\n\t1223 -> 1178 [penwidth=1, color=black];\n\t1223 -> 1179 [penwidth=1, color=black];\n\t1223 -> 1180 [penwidth=1, color=black];\n\t1223 -> 1181 [penwidth=1, color=black];\n\t1223 -> 1182 [penwidth=1, color=black];\n\t1223 -> 1183 [penwidth=1, color=black];\n\t1223 -> 1184 [penwidth=1, color=black];\n\t1223 -> 1185 [penwidth=1, color=black];\n\t1223 -> 1186 [penwidth=1, color=black];\n\t1223 -> 1189 [penwidth=1, color=black];\n\t1223 -> 1190 [penwidth=1, color=black];\n\t1223 -> 1191 [penwidth=1, color=black];\n\t1223 -> 1192 [penwidth=1, color=black];\n\t1223 -> 1193 [penwidth=1, color=black];\n\t1223 -> 1194 [penwidth=1, color=black];\n\t1227 -> 612 [penwidth=1, color=black];\n\t1227 -> 613 [penwidth=1, color=black];\n\t1227 -> 614 [penwidth=1, color=black];\n\t1227 -> 615 [penwidth=1, color=black];\n\t1227 -> 616 [penwidth=1, color=black];\n\t1227 -> 617 [penwidth=1, color=black];\n\t1227 -> 618 [penwidth=1, color=black];\n\t1227 -> 619 [penwidth=1, color=black];\n\t1227 -> 620 [penwidth=1, color=black];\n\t1227 -> 621 [penwidth=1, color=black];\n\t1227 -> 622 [penwidth=1, color=black];\n\t1227 -> 623 [penwidth=1, color=black];\n\t1227 -> 624 [penwidth=1, color=black];\n\t1227 -> 625 [penwidth=1, color=black];\n\t1227 -> 626 [penwidth=1, color=black];\n\t1227 -> 627 [penwidth=1, color=black];\n\t1227 -> 628 [penwidth=1, color=black];\n\t1227 -> 629 [penwidth=1, color=black];\n\t1227 -> 630 [penwidth=1, color=black];\n\t1227 -> 631 [penwidth=1, color=black];\n\t1227 -> 632 [penwidth=1, color=black];\n\t1227 -> 633 [penwidth=1, color=black];\n\t1227 -> 634 [penwidth=1, color=black];\n\t1227 -> 635 [penwidth=1, color=black];\n\t1227 -> 636 [penwidth=1, color=black];\n\t1227 -> 637 [penwidth=1, color=black];\n\t1227 -> 638 [penwidth=1, color=black];\n\t1227 -> 639 [penwidth=1, color=black];\n\t1227 -> 640 [penwidth=1, color=black];\n\t1227 -> 641 [penwidth=1, color=black];\n\t1227 -> 646 [penwidth=1, color=black];\n\t1227 -> 647 [penwidth=1, color=black];\n\t1227 -> 648 [penwidth=1, color=black];\n\t1227 -> 649 [penwidth=1, color=black];\n\t1227 -> 650 [penwidth=1, color=black];\n\t1227 -> 653 [penwidth=1, color=black];\n\t1227 -> 654 [penwidth=1, color=black];\n\t1227 -> 655 [penwidth=1, color=black];\n\t1227 -> 656 [penwidth=1, color=black];\n\t1227 -> 657 [penwidth=1, color=black];\n\t1227 -> 658 [penwidth=1, color=black];\n\t1227 -> 659 [penwidth=1, color=black];\n\t1227 -> 660 [penwidth=1, color=black];\n\t1227 -> 661 [penwidth=1, color=black];\n\t1227 -> 662 [penwidth=1, color=black];\n\t1227 -> 663 [penwidth=1, color=black];\n\t1227 -> 664 [penwidth=1, color=black];\n\t1227 -> 665 [penwidth=1, color=black];\n\t1227 -> 666 [penwidth=1, color=black];\n\t1227 -> 667 [penwidth=1, color=black];\n\t1227 -> 668 [penwidth=1, color=black];\n\t1227 -> 669 [penwidth=1, color=black];\n\t1227 -> 670 [penwidth=1, color=black];\n\t1227 -> 671 [penwidth=1, color=black];\n\t1227 -> 672 [penwidth=1, color=black];\n\t1227 -> 673 [penwidth=1, color=black];\n\t1227 -> 674 [penwidth=1, color=black];\n\t1227 -> 675 [penwidth=1, color=black];\n\t1227 -> 676 [penwidth=1, color=black];\n\t1227 -> 677 [penwidth=1, color=black];\n\t1227 -> 678 [penwidth=1, color=black];\n\t1227 -> 679 [penwidth=1, color=black];\n\t1227 -> 680 [penwidth=1, color=black];\n\t1227 -> 681 [penwidth=1, color=black];\n\t1227 -> 682 [penwidth=1, color=black];\n\t1227 -> 683 [penwidth=1, color=black];\n\t1227 -> 684 [penwidth=1, color=black];\n\t1227 -> 685 [penwidth=1, color=black];\n\t1227 -> 686 [penwidth=1, color=black];\n\t1227 -> 687 [penwidth=1, color=black];\n\t1227 -> 688 [penwidth=1, color=black];\n\t1227 -> 689 [penwidth=1, color=black];\n\t1227 -> 691 [penwidth=1, color=black];\n\t1227 -> 692 [penwidth=1, color=black];\n\t1227 -> 693 [penwidth=1, color=black];\n\t1227 -> 694 [penwidth=1, color=black];\n\t1227 -> 695 [penwidth=1, color=black];\n\t1227 -> 696 [penwidth=1, color=black];\n\t1227 -> 697 [penwidth=1, color=black];\n\t1227 -> 698 [penwidth=1, color=black];\n\t1227 -> 699 [penwidth=1, color=black];\n\t1227 -> 700 [penwidth=1, color=black];\n\t1227 -> 701 [penwidth=1, color=black];\n\t1227 -> 702 [penwidth=1, color=black];\n\t1227 -> 703 [penwidth=1, color=black];\n\t1227 -> 704 [penwidth=1, color=black];\n\t1227 -> 705 [penwidth=1, color=black];\n\t1227 -> 706 [penwidth=1, color=black];\n\t1227 -> 707 [penwidth=1, color=black];\n\t1227 -> 708 [penwidth=1, color=black];\n\t1227 -> 709 [penwidth=1, color=black];\n\t1227 -> 710 [penwidth=1, color=black];\n\t1227 -> 711 [penwidth=1, color=black];\n\t1227 -> 712 [penwidth=1, color=black];\n\t1227 -> 713 [penwidth=1, color=black];\n\t1227 -> 714 [penwidth=1, color=black];\n\t1227 -> 715 [penwidth=1, color=black];\n\t1227 -> 716 [penwidth=1, color=black];\n\t1227 -> 717 [penwidth=1, color=black];\n\t1227 -> 718 [penwidth=1, color=black];\n\t1227 -> 719 [penwidth=1, color=black];\n\t1227 -> 720 [penwidth=1, color=black];\n\t1227 -> 721 [penwidth=1, color=black];\n\t1227 -> 722 [penwidth=1, color=black];\n\t1227 -> 723 [penwidth=1, color=black];\n\t1227 -> 724 [penwidth=1, color=black];\n\t1227 -> 725 [penwidth=1, color=black];\n\t1227 -> 726 [penwidth=1, color=black];\n\t1227 -> 727 [penwidth=1, color=black];\n\t1227 -> 728 [penwidth=1, color=black];\n\t1227 -> 729 [penwidth=1, color=black];\n\t1227 -> 730 [penwidth=1, color=black];\n\t1227 -> 731 [penwidth=1, color=black];\n\t1227 -> 732 [penwidth=1, color=black];\n\t1227 -> 733 [penwidth=1, color=black];\n\t1227 -> 734 [penwidth=1, color=black];\n\t1227 -> 735 [penwidth=1, color=black];\n\t1227 -> 736 [penwidth=1, color=black];\n\t1227 -> 737 [penwidth=1, color=black];\n\t1227 -> 738 [penwidth=1, color=black];\n\t1227 -> 739 [penwidth=1, color=black];\n\t1227 -> 740 [penwidth=1, color=black];\n\t1227 -> 741 [penwidth=1, color=black];\n\t1227 -> 742 [penwidth=1, color=black];\n\t1227 -> 743 [penwidth=1, color=black];\n\t1227 -> 744 [penwidth=1, color=black];\n\t1227 -> 745 [penwidth=1, color=black];\n\t1227 -> 746 [penwidth=1, color=black];\n\t1227 -> 747 [penwidth=1, color=black];\n\t1227 -> 748 [penwidth=1, color=black];\n\t1227 -> 749 [penwidth=1, color=black];\n\t1227 -> 750 [penwidth=1, color=black];\n\t1227 -> 751 [penwidth=1, color=black];\n\t1227 -> 753 [penwidth=1, color=black];\n\t1227 -> 754 [penwidth=1, color=black];\n\t1227 -> 755 [penwidth=1, color=black];\n\t1227 -> 756 [penwidth=1, color=black];\n\t1227 -> 757 [penwidth=1, color=black];\n\t1227 -> 758 [penwidth=1, color=black];\n\t1227 -> 759 [penwidth=1, color=black];\n\t1227 -> 760 [penwidth=1, color=black];\n\t1227 -> 761 [penwidth=1, color=black];\n\t1227 -> 762 [penwidth=1, color=black];\n\t1227 -> 763 [penwidth=1, color=black];\n\t1227 -> 764 [penwidth=1, color=black];\n\t1227 -> 765 [penwidth=1, color=black];\n\t1227 -> 766 [penwidth=1, color=black];\n\t1227 -> 767 [penwidth=1, color=black];\n\t1227 -> 768 [penwidth=1, color=black];\n\t1227 -> 769 [penwidth=1, color=black];\n\t1227 -> 770 [penwidth=1, color=black];\n\t1227 -> 771 [penwidth=1, color=black];\n\t1227 -> 772 [penwidth=1, color=black];\n\t1227 -> 773 [penwidth=1, color=black];\n\t1227 -> 774 [penwidth=1, color=black];\n\t1227 -> 775 [penwidth=1, color=black];\n\t1227 -> 776 [penwidth=1, color=black];\n\t1227 -> 777 [penwidth=1, color=black];\n\t1227 -> 778 [penwidth=1, color=black];\n\t1227 -> 779 [penwidth=1, color=black];\n\t1227 -> 780 [penwidth=1, color=black];\n\t1227 -> 781 [penwidth=1, color=black];\n\t1227 -> 782 [penwidth=1, color=black];\n\t1227 -> 783 [penwidth=1, color=black];\n\t1227 -> 784 [penwidth=1, color=black];\n\t1227 -> 785 [penwidth=1, color=black];\n\t1227 -> 786 [penwidth=1, color=black];\n\t1227 -> 787 [penwidth=1, color=black];\n\t1227 -> 788 [penwidth=1, color=black];\n\t1227 -> 789 [penwidth=1, color=black];\n\t1227 -> 790 [penwidth=1, color=black];\n\t1227 -> 791 [penwidth=1, color=black];\n\t1227 -> 792 [penwidth=1, color=black];\n\t1227 -> 793 [penwidth=1, color=black];\n\t1227 -> 794 [penwidth=1, color=black];\n\t1227 -> 795 [penwidth=1, color=black];\n\t1227 -> 796 [penwidth=1, color=black];\n\t1227 -> 797 [penwidth=1, color=black];\n\t1227 -> 798 [penwidth=1, color=black];\n\t1227 -> 799 [penwidth=1, color=black];\n\t1227 -> 800 [penwidth=1, color=black];\n\t1227 -> 801 [penwidth=1, color=black];\n\t1227 -> 802 [penwidth=1, color=black];\n\t1227 -> 803 [penwidth=1, color=black];\n\t1227 -> 804 [penwidth=1, color=black];\n\t1227 -> 805 [penwidth=1, color=black];\n\t1227 -> 806 [penwidth=1, color=black];\n\t1227 -> 807 [penwidth=1, color=black];\n\t1227 -> 808 [penwidth=1, color=black];\n\t1227 -> 809 [penwidth=1, color=black];\n\t1227 -> 810 [penwidth=1, color=black];\n\t1227 -> 811 [penwidth=1, color=black];\n\t1227 -> 812 [penwidth=1, color=black];\n\t1227 -> 813 [penwidth=1, color=black];\n\t1227 -> 814 [penwidth=1, color=black];\n\t1227 -> 815 [penwidth=1, color=black];\n\t1227 -> 816 [penwidth=1, color=black];\n\t1227 -> 817 [penwidth=1, color=black];\n\t1227 -> 818 [penwidth=1, color=black];\n\t1227 -> 819 [penwidth=1, color=black];\n\t1227 -> 820 [penwidth=1, color=black];\n\t1227 -> 821 [penwidth=1, color=black];\n\t1227 -> 822 [penwidth=1, color=black];\n\t1227 -> 823 [penwidth=1, color=black];\n\t1227 -> 824 [penwidth=1, color=black];\n\t1227 -> 825 [penwidth=1, color=black];\n\t1227 -> 826 [penwidth=1, color=black];\n\t1227 -> 827 [penwidth=1, color=black];\n\t1227 -> 828 [penwidth=1, color=black];\n\t1227 -> 829 [penwidth=1, color=black];\n\t1227 -> 830 [penwidth=1, color=black];\n\t1227 -> 831 [penwidth=1, color=black];\n\t1227 -> 832 [penwidth=1, color=black];\n\t1227 -> 833 [penwidth=1, color=black];\n\t1227 -> 834 [penwidth=1, color=black];\n\t1227 -> 835 [penwidth=1, color=black];\n\t1227 -> 836 [penwidth=1, color=black];\n\t1227 -> 837 [penwidth=1, color=black];\n\t1227 -> 838 [penwidth=1, color=black];\n\t1227 -> 839 [penwidth=1, color=black];\n\t1227 -> 840 [penwidth=1, color=black];\n\t1227 -> 841 [penwidth=1, color=black];\n\t1227 -> 842 [penwidth=1, color=black];\n\t1227 -> 843 [penwidth=1, color=black];\n\t1227 -> 844 [penwidth=1, color=black];\n\t1227 -> 845 [penwidth=1, color=black];\n\t1227 -> 846 [penwidth=1, color=black];\n\t1227 -> 847 [penwidth=1, color=black];\n\t1227 -> 848 [penwidth=1, color=black];\n\t1227 -> 849 [penwidth=1, color=black];\n\t1227 -> 850 [penwidth=1, color=black];\n\t1227 -> 851 [penwidth=1, color=black];\n\t1227 -> 852 [penwidth=1, color=black];\n\t1227 -> 853 [penwidth=1, color=black];\n\t1227 -> 854 [penwidth=1, color=black];\n\t1227 -> 855 [penwidth=1, color=black];\n\t1227 -> 856 [penwidth=1, color=black];\n\t1227 -> 857 [penwidth=1, color=black];\n\t1227 -> 858 [penwidth=1, color=black];\n\t1227 -> 859 [penwidth=1, color=black];\n\t1227 -> 860 [penwidth=1, color=black];\n\t1227 -> 861 [penwidth=1, color=black];\n\t1227 -> 862 [penwidth=1, color=black];\n\t1227 -> 863 [penwidth=1, color=black];\n\t1227 -> 864 [penwidth=1, color=black];\n\t1227 -> 865 [penwidth=1, color=black];\n\t1227 -> 866 [penwidth=1, color=black];\n\t1227 -> 867 [penwidth=1, color=black];\n\t1227 -> 868 [penwidth=1, color=black];\n\t1227 -> 869 [penwidth=1, color=black];\n\t1227 -> 870 [penwidth=1, color=black];\n\t1227 -> 874 [penwidth=1, color=black];\n\t1227 -> 875 [penwidth=1, color=black];\n\t1227 -> 876 [penwidth=1, color=black];\n\t1227 -> 877 [penwidth=1, color=black];\n\t1227 -> 878 [penwidth=1, color=black];\n\t1227 -> 879 [penwidth=1, color=black];\n\t1227 -> 880 [penwidth=1, color=black];\n\t1227 -> 881 [penwidth=1, color=black];\n\t1227 -> 882 [penwidth=1, color=black];\n\t1227 -> 883 [penwidth=1, color=black];\n\t1227 -> 884 [penwidth=1, color=black];\n\t1227 -> 885 [penwidth=1, color=black];\n\t1227 -> 886 [penwidth=1, color=black];\n\t1227 -> 887 [penwidth=1, color=black];\n\t1227 -> 888 [penwidth=1, color=black];\n\t1227 -> 889 [penwidth=1, color=black];\n\t1227 -> 890 [penwidth=1, color=black];\n\t1227 -> 891 [penwidth=1, color=black];\n\t1227 -> 892 [penwidth=1, color=black];\n\t1227 -> 893 [penwidth=1, color=black];\n\t1227 -> 894 [penwidth=1, color=black];\n\t1227 -> 895 [penwidth=1, color=black];\n\t1227 -> 896 [penwidth=1, color=black];\n\t1227 -> 897 [penwidth=1, color=black];\n\t1227 -> 898 [penwidth=1, color=black];\n\t1227 -> 899 [penwidth=1, color=black];\n\t1227 -> 900 [penwidth=1, color=black];\n\t1227 -> 901 [penwidth=1, color=black];\n\t1227 -> 902 [penwidth=1, color=black];\n\t1227 -> 903 [penwidth=1, color=black];\n\t1227 -> 904 [penwidth=1, color=black];\n\t1227 -> 905 [penwidth=1, color=black];\n\t1227 -> 906 [penwidth=1, color=black];\n\t1227 -> 907 [penwidth=1, color=black];\n\t1227 -> 908 [penwidth=1, color=black];\n\t1227 -> 909 [penwidth=1, color=black];\n\t1227 -> 910 [penwidth=1, color=black];\n\t1227 -> 911 [penwidth=1, color=black];\n\t1227 -> 912 [penwidth=1, color=black];\n\t1227 -> 913 [penwidth=1, color=black];\n\t1227 -> 914 [penwidth=1, color=black];\n\t1227 -> 915 [penwidth=1, color=black];\n\t1227 -> 916 [penwidth=1, color=black];\n\t1227 -> 917 [penwidth=1, color=black];\n\t1227 -> 918 [penwidth=1, color=black];\n\t1227 -> 919 [penwidth=1, color=black];\n\t1227 -> 920 [penwidth=1, color=black];\n\t1227 -> 921 [penwidth=1, color=black];\n\t1227 -> 922 [penwidth=1, color=black];\n\t1227 -> 923 [penwidth=1, color=black];\n\t1227 -> 924 [penwidth=1, color=black];\n\t1227 -> 925 [penwidth=1, color=black];\n\t1227 -> 926 [penwidth=1, color=black];\n\t1227 -> 927 [penwidth=1, color=black];\n\t1227 -> 928 [penwidth=1, color=black];\n\t1227 -> 929 [penwidth=1, color=black];\n\t1227 -> 930 [penwidth=1, color=black];\n\t1227 -> 931 [penwidth=1, color=black];\n\t1227 -> 932 [penwidth=1, color=black];\n\t1227 -> 933 [penwidth=1, color=black];\n\t1227 -> 934 [penwidth=1, color=black];\n\t1227 -> 935 [penwidth=1, color=black];\n\t1227 -> 936 [penwidth=1, color=black];\n\t1227 -> 937 [penwidth=1, color=black];\n\t1227 -> 938 [penwidth=1, color=black];\n\t1227 -> 939 [penwidth=1, color=black];\n\t1227 -> 940 [penwidth=1, color=black];\n\t1227 -> 941 [penwidth=1, color=black];\n\t1227 -> 942 [penwidth=1, color=black];\n\t1227 -> 943 [penwidth=1, color=black];\n\t1227 -> 944 [penwidth=1, color=black];\n\t1227 -> 945 [penwidth=1, color=black];\n\t1227 -> 946 [penwidth=1, color=black];\n\t1227 -> 947 [penwidth=1, color=black];\n\t1227 -> 948 [penwidth=1, color=black];\n\t1227 -> 949 [penwidth=1, color=black];\n\t1227 -> 950 [penwidth=1, color=black];\n\t1227 -> 951 [penwidth=1, color=black];\n\t1227 -> 952 [penwidth=1, color=black];\n\t1227 -> 953 [penwidth=1, color=black];\n\t1227 -> 954 [penwidth=1, color=black];\n\t1227 -> 955 [penwidth=1, color=black];\n\t1227 -> 956 [penwidth=1, color=black];\n\t1227 -> 957 [penwidth=1, color=black];\n\t1227 -> 958 [penwidth=1, color=black];\n\t1227 -> 959 [penwidth=1, color=black];\n\t1227 -> 960 [penwidth=1, color=black];\n\t1227 -> 961 [penwidth=1, color=black];\n\t1227 -> 962 [penwidth=1, color=black];\n\t1227 -> 963 [penwidth=1, color=black];\n\t1227 -> 964 [penwidth=1, color=black];\n\t1227 -> 965 [penwidth=1, color=black];\n\t1227 -> 966 [penwidth=1, color=black];\n\t1227 -> 967 [penwidth=1, color=black];\n\t1227 -> 968 [penwidth=1, color=black];\n\t1227 -> 969 [penwidth=1, color=black];\n\t1227 -> 970 [penwidth=1, color=black];\n\t1227 -> 971 [penwidth=1, color=black];\n\t1227 -> 972 [penwidth=1, color=black];\n\t1227 -> 973 [penwidth=1, color=black];\n\t1227 -> 974 [penwidth=1, color=black];\n\t1227 -> 975 [penwidth=1, color=black];\n\t1227 -> 976 [penwidth=1, color=black];\n\t1227 -> 977 [penwidth=1, color=black];\n\t1227 -> 978 [penwidth=1, color=black];\n\t1227 -> 979 [penwidth=1, color=black];\n\t1227 -> 980 [penwidth=1, color=black];\n\t1227 -> 981 [penwidth=1, color=black];\n\t1227 -> 982 [penwidth=1, color=black];\n\t1227 -> 983 [penwidth=1, color=black];\n\t1227 -> 984 [penwidth=1, color=black];\n\t1227 -> 985 [penwidth=1, color=black];\n\t1227 -> 986 [penwidth=1, color=black];\n\t1227 -> 987 [penwidth=1, color=black];\n\t1227 -> 988 [penwidth=1, color=black];\n\t1227 -> 989 [penwidth=1, color=black];\n\t1227 -> 990 [penwidth=1, color=black];\n\t1227 -> 991 [penwidth=1, color=black];\n\t1227 -> 992 [penwidth=1, color=black];\n\t1227 -> 993 [penwidth=1, color=black];\n\t1227 -> 994 [penwidth=1, color=black];\n\t1227 -> 995 [penwidth=1, color=black];\n\t1227 -> 996 [penwidth=1, color=black];\n\t1227 -> 997 [penwidth=1, color=black];\n\t1227 -> 998 [penwidth=1, color=black];\n\t1227 -> 999 [penwidth=1, color=black];\n\t1227 -> 1000 [penwidth=1, color=black];\n\t1227 -> 1001 [penwidth=1, color=black];\n\t1227 -> 1002 [penwidth=1, color=black];\n\t1227 -> 1003 [penwidth=1, color=black];\n\t1227 -> 1004 [penwidth=1, color=black];\n\t1227 -> 1005 [penwidth=1, color=black];\n\t1227 -> 1006 [penwidth=1, color=black];\n\t1227 -> 1007 [penwidth=1, color=black];\n\t1227 -> 1008 [penwidth=1, color=black];\n\t1227 -> 1009 [penwidth=1, color=black];\n\t1227 -> 1010 [penwidth=1, color=black];\n\t1227 -> 1011 [penwidth=1, color=black];\n\t1227 -> 1012 [penwidth=1, color=black];\n\t1227 -> 1013 [penwidth=1, color=black];\n\t1227 -> 1014 [penwidth=1, color=black];\n\t1227 -> 1015 [penwidth=1, color=black];\n\t1227 -> 1016 [penwidth=1, color=black];\n\t1227 -> 1017 [penwidth=1, color=black];\n\t1227 -> 1019 [penwidth=1, color=black];\n\t1227 -> 1020 [penwidth=1, color=black];\n\t1227 -> 1021 [penwidth=1, color=black];\n\t1227 -> 1022 [penwidth=1, color=black];\n\t1227 -> 1023 [penwidth=1, color=black];\n\t1227 -> 1026 [penwidth=1, color=black];\n\t1227 -> 1027 [penwidth=1, color=black];\n\t1227 -> 1028 [penwidth=1, color=black];\n\t1227 -> 1029 [penwidth=1, color=black];\n\t1227 -> 1030 [penwidth=1, color=black];\n\t1227 -> 1031 [penwidth=1, color=black];\n\t1227 -> 1032 [penwidth=1, color=black];\n\t1227 -> 1033 [penwidth=1, color=black];\n\t1227 -> 1034 [penwidth=1, color=black];\n\t1227 -> 1035 [penwidth=1, color=black];\n\t1227 -> 1036 [penwidth=1, color=black];\n\t1227 -> 1037 [penwidth=1, color=black];\n\t1227 -> 1038 [penwidth=1, color=black];\n\t1227 -> 1039 [penwidth=1, color=black];\n\t1227 -> 1040 [penwidth=1, color=black];\n\t1227 -> 1041 [penwidth=1, color=black];\n\t1227 -> 1042 [penwidth=1, color=black];\n\t1227 -> 1045 [penwidth=1, color=black];\n\t1227 -> 1046 [penwidth=1, color=black];\n\t1227 -> 1047 [penwidth=1, color=black];\n\t1227 -> 1048 [penwidth=1, color=black];\n\t1227 -> 1049 [penwidth=1, color=black];\n\t1227 -> 1050 [penwidth=1, color=black];\n\t1227 -> 1051 [penwidth=1, color=black];\n\t1227 -> 1052 [penwidth=1, color=black];\n\t1227 -> 1053 [penwidth=1, color=black];\n\t1227 -> 1054 [penwidth=1, color=black];\n\t1227 -> 1055 [penwidth=1, color=black];\n\t1227 -> 1057 [penwidth=1, color=black];\n\t1227 -> 1058 [penwidth=1, color=black];\n\t1227 -> 1059 [penwidth=1, color=black];\n\t1227 -> 1060 [penwidth=1, color=black];\n\t1227 -> 1061 [penwidth=1, color=black];\n\t1227 -> 1062 [penwidth=1, color=black];\n\t1227 -> 1068 [penwidth=1, color=black];\n\t1227 -> 1069 [penwidth=1, color=black];\n\t1227 -> 1070 [penwidth=1, color=black];\n\t1227 -> 1071 [penwidth=1, color=black];\n\t1227 -> 1072 [penwidth=1, color=black];\n\t1227 -> 1081 [penwidth=1, color=black];\n\t1227 -> 1082 [penwidth=1, color=black];\n\t1227 -> 1083 [penwidth=1, color=black];\n\t1227 -> 1084 [penwidth=1, color=black];\n\t1227 -> 1085 [penwidth=1, color=black];\n\t1227 -> 1087 [penwidth=1, color=black];\n\t1227 -> 1088 [penwidth=1, color=black];\n\t1227 -> 1089 [penwidth=1, color=black];\n\t1227 -> 1090 [penwidth=1, color=black];\n\t1227 -> 1091 [penwidth=1, color=black];\n\t1227 -> 1092 [penwidth=1, color=black];\n\t1227 -> 1093 [penwidth=1, color=black];\n\t1227 -> 1094 [penwidth=1, color=black];\n\t1227 -> 1095 [penwidth=1, color=black];\n\t1227 -> 1096 [penwidth=1, color=black];\n\t1227 -> 1097 [penwidth=1, color=black];\n\t1227 -> 1098 [penwidth=1, color=black];\n\t1227 -> 1099 [penwidth=1, color=black];\n\t1227 -> 1100 [penwidth=1, color=black];\n\t1227 -> 1101 [penwidth=1, color=black];\n\t1227 -> 1102 [penwidth=1, color=black];\n\t1227 -> 1103 [penwidth=1, color=black];\n\t1227 -> 1104 [penwidth=1, color=black];\n\t1227 -> 1105 [penwidth=1, color=black];\n\t1227 -> 1106 [penwidth=1, color=black];\n\t1227 -> 1107 [penwidth=1, color=black];\n\t1227 -> 1108 [penwidth=1, color=black];\n\t1227 -> 1109 [penwidth=1, color=black];\n\t1227 -> 1110 [penwidth=1, color=black];\n\t1227 -> 1111 [penwidth=1, color=black];\n\t1227 -> 1112 [penwidth=1, color=black];\n\t1227 -> 1113 [penwidth=1, color=black];\n\t1227 -> 1117 [penwidth=1, color=black];\n\t1227 -> 1118 [penwidth=1, color=black];\n\t1227 -> 1119 [penwidth=1, color=black];\n\t1227 -> 1120 [penwidth=1, color=black];\n\t1227 -> 1121 [penwidth=1, color=black];\n\t1227 -> 1122 [penwidth=1, color=black];\n\t1227 -> 1123 [penwidth=1, color=black];\n\t1227 -> 1124 [penwidth=1, color=black];\n\t1227 -> 1125 [penwidth=1, color=black];\n\t1227 -> 1126 [penwidth=1, color=black];\n\t1227 -> 1127 [penwidth=1, color=black];\n\t1227 -> 1128 [penwidth=1, color=black];\n\t1227 -> 1129 [penwidth=1, color=black];\n\t1227 -> 1130 [penwidth=1, color=black];\n\t1227 -> 1131 [penwidth=1, color=black];\n\t1227 -> 1132 [penwidth=1, color=black];\n\t1227 -> 1133 [penwidth=1, color=black];\n\t1227 -> 1134 [penwidth=1, color=black];\n\t1227 -> 1135 [penwidth=1, color=black];\n\t1227 -> 1136 [penwidth=1, color=black];\n\t1227 -> 1137 [penwidth=1, color=black];\n\t1227 -> 1138 [penwidth=1, color=black];\n\t1227 -> 1139 [penwidth=1, color=black];\n\t1227 -> 1140 [penwidth=1, color=black];\n\t1227 -> 1141 [penwidth=1, color=black];\n\t1227 -> 1143 [penwidth=1, color=black];\n\t1227 -> 1144 [penwidth=1, color=black];\n\t1227 -> 1145 [penwidth=1, color=black];\n\t1227 -> 1146 [penwidth=1, color=black];\n\t1227 -> 1147 [penwidth=1, color=black];\n\t1227 -> 1148 [penwidth=1, color=black];\n\t1227 -> 1149 [penwidth=1, color=black];\n\t1227 -> 1150 [penwidth=1, color=black];\n\t1227 -> 1151 [penwidth=1, color=black];\n\t1227 -> 1152 [penwidth=1, color=black];\n\t1227 -> 1153 [penwidth=1, color=black];\n\t1227 -> 1154 [penwidth=1, color=black];\n\t1227 -> 1155 [penwidth=1, color=black];\n\t1227 -> 1156 [penwidth=1, color=black];\n\t1227 -> 1157 [penwidth=1, color=black];\n\t1227 -> 1158 [penwidth=1, color=black];\n\t1227 -> 1159 [penwidth=1, color=black];\n\t1227 -> 1160 [penwidth=1, color=black];\n\t1227 -> 1161 [penwidth=1, color=black];\n\t1227 -> 1162 [penwidth=1, color=black];\n\t1227 -> 1163 [penwidth=1, color=black];\n\t1227 -> 1164 [penwidth=1, color=black];\n\t1227 -> 1165 [penwidth=1, color=black];\n\t1227 -> 1166 [penwidth=1, color=black];\n\t1227 -> 1167 [penwidth=1, color=black];\n\t1227 -> 1168 [penwidth=1, color=black];\n\t1227 -> 1169 [penwidth=1, color=black];\n\t1227 -> 1170 [penwidth=1, color=black];\n\t1227 -> 1171 [penwidth=1, color=black];\n\t1227 -> 1172 [penwidth=1, color=black];\n\t1227 -> 1173 [penwidth=1, color=black];\n\t1227 -> 1174 [penwidth=1, color=black];\n\t1227 -> 1175 [penwidth=1, color=black];\n\t1227 -> 1176 [penwidth=1, color=black];\n\t1227 -> 1177 [penwidth=1, color=black];\n\t1227 -> 1178 [penwidth=1, color=black];\n\t1227 -> 1179 [penwidth=1, color=black];\n\t1227 -> 1180 [penwidth=1, color=black];\n\t1227 -> 1181 [penwidth=1, color=black];\n\t1227 -> 1182 [penwidth=1, color=black];\n\t1227 -> 1183 [penwidth=1, color=black];\n\t1227 -> 1184 [penwidth=1, color=black];\n\t1227 -> 1185 [penwidth=1, color=black];\n\t1227 -> 1186 [penwidth=1, color=black];\n\t1227 -> 1189 [penwidth=1, color=black];\n\t1227 -> 1190 [penwidth=1, color=black];\n\t1227 -> 1191 [penwidth=1, color=black];\n\t1227 -> 1192 [penwidth=1, color=black];\n\t1227 -> 1193 [penwidth=1, color=black];\n\t1227 -> 1194 [penwidth=1, color=black];\n\t1272 -> 1273 [penwidth=1, color=black];\n\t1273 -> 1275 [penwidth=1, color=black];\n\t1274 -> 1273 [penwidth=1, color=black];\n\t1276 -> 1275 [penwidth=1, color=black];\n\t1291 -> 1435 [penwidth=\"1.6931471805599454\", color=black];\n\t1292 -> 1370 [penwidth=1, color=black];\n\t1292 -> 1371 [penwidth=1, color=black];\n\t1292 -> 1373 [penwidth=1, color=black];\n\t1292 -> 1387 [penwidth=1, color=black];\n\t1292 -> 1392 [penwidth=1, color=black];\n\t1292 -> 1433 [penwidth=1, color=black];\n\t1292 -> 1439 [penwidth=1, color=black];\n\t1293 -> 1294 [penwidth=1, color=black];\n\t1293 -> 1416 [penwidth=1, color=black];\n\t1294 -> 1395 [penwidth=1, color=black];\n\t1294 -> 1429 [penwidth=1, color=black];\n\t1294 -> 1433 [penwidth=1, color=black];\n\t1295 -> 1296 [penwidth=1, color=black];\n\t1296 -> 1370 [penwidth=1, color=black];\n\t1296 -> 1371 [penwidth=\"1.6931471805599454\", color=black];\n\t1296 -> 1373 [penwidth=1, color=black];\n\t1296 -> 1387 [penwidth=1, color=black];\n\t1296 -> 1392 [penwidth=\"1.6931471805599454\", color=black];\n\t1296 -> 1433 [penwidth=1, color=black];\n\t1296 -> 1439 [penwidth=1, color=black];\n\t1301 -> 1229 [penwidth=1, color=black];\n\t1301 -> 1230 [penwidth=1, color=black];\n\t1301 -> 1232 [penwidth=1, color=black];\n\t1301 -> 1234 [penwidth=1, color=black];\n\t1301 -> 1435 [penwidth=\"2.386294361119891\", color=black];\n\t1302 -> 1236 [penwidth=1, color=black];\n\t1302 -> 1237 [penwidth=1, color=black];\n\t1302 -> 1238 [penwidth=1, color=black];\n\t1302 -> 1239 [penwidth=1, color=black];\n\t1302 -> 1240 [penwidth=1, color=black];\n\t1302 -> 1241 [penwidth=1, color=black];\n\t1302 -> 1242 [penwidth=1, color=black];\n\t1302 -> 1243 [penwidth=1, color=black];\n\t1302 -> 1244 [penwidth=1, color=black];\n\t1302 -> 1248 [penwidth=1, color=black];\n\t1302 -> 1249 [penwidth=1, color=black];\n\t1302 -> 1251 [penwidth=1, color=black];\n\t1302 -> 1252 [penwidth=1, color=black];\n\t1302 -> 1258 [penwidth=1, color=black];\n\t1302 -> 1259 [penwidth=1, color=black];\n\t1302 -> 1261 [penwidth=1, color=black];\n\t1302 -> 1262 [penwidth=1, color=black];\n\t1302 -> 1264 [penwidth=1, color=black];\n\t1302 -> 1267 [penwidth=1, color=black];\n\t1302 -> 1269 [penwidth=\"1.6931471805599454\", color=black];\n\t1302 -> 1270 [penwidth=1, color=black];\n\t1302 -> 1271 [penwidth=1, color=black];\n\t1302 -> 1291 [penwidth=1, color=black];\n\t1302 -> 1293 [penwidth=\"3.70805020110221\", color=black];\n\t1302 -> 1294 [penwidth=\"3.0794415416798357\", color=black];\n\t1302 -> 1325 [penwidth=\"2.9459101490553135\", color=black];\n\t1302 -> 1350 [penwidth=1, color=black];\n\t1303 -> 1254 [penwidth=1, color=black];\n\t1303 -> 1255 [penwidth=1, color=black];\n\t1303 -> 1296 [penwidth=1, color=black];\n\t1303 -> 1442 [penwidth=1, color=black];\n\t1304 -> 1253 [penwidth=1, color=black];\n\t1304 -> 1292 [penwidth=1, color=black];\n\t1304 -> 1442 [penwidth=1, color=black];\n\t1305 -> 1266 [penwidth=1, color=black];\n\t1305 -> 1268 [penwidth=1, color=black];\n\t1306 -> 1260 [penwidth=1, color=black];\n\t1306 -> 1296 [penwidth=1, color=black];\n\t1306 -> 1442 [penwidth=1, color=black];\n\t1307 -> 1245 [penwidth=1, color=black];\n\t1307 -> 1246 [penwidth=1, color=black];\n\t1307 -> 1247 [penwidth=1, color=black];\n\t1307 -> 1256 [penwidth=1, color=black];\n\t1307 -> 1263 [penwidth=1, color=black];\n\t1307 -> 1435 [penwidth=\"2.6094379124341005\", color=black];\n\t1308 -> 1233 [penwidth=1, color=black];\n\t1308 -> 1295 [penwidth=1, color=black];\n\t1308 -> 1296 [penwidth=1, color=black];\n\t1308 -> 1323 [penwidth=1, color=black];\n\t1308 -> 1442 [penwidth=\"2.09861228866811\", color=black];\n\t1309 -> 1250 [penwidth=1, color=black];\n\t1309 -> 1257 [penwidth=1, color=black];\n\t1309 -> 1265 [penwidth=1, color=black];\n\t1309 -> 1292 [penwidth=1, color=black];\n\t1309 -> 1295 [penwidth=1, color=black];\n\t1309 -> 1327 [penwidth=1, color=black];\n\t1310 -> 1228 [penwidth=1, color=black];\n\t1310 -> 1231 [penwidth=1, color=black];\n\t1310 -> 1235 [penwidth=1, color=black];\n\t1310 -> 1435 [penwidth=\"2.09861228866811\", color=black];\n\t1311 -> 1370 [penwidth=1, color=black];\n\t1312 -> 1371 [penwidth=1, color=black];\n\t1312 -> 1442 [penwidth=1, color=black];\n\t1313 -> 1371 [penwidth=1, color=black];\n\t1313 -> 1442 [penwidth=1, color=black];\n\t1315 -> 1871 [penwidth=1, color=black];\n\t1316 -> 1321 [penwidth=1, color=black];\n\t1317 -> 1454 [penwidth=1, color=black];\n\t1317 -> 1456 [penwidth=1, color=black];\n\t1317 -> 1470 [penwidth=1, color=black];\n\t1318 -> 1319 [penwidth=1, color=black];\n\t1318 -> 1475 [penwidth=1, color=black];\n\t1320 -> 1321 [penwidth=1, color=black];\n\t1321 -> 1454 [penwidth=\"1.6931471805599454\", color=black];\n\t1321 -> 1456 [penwidth=1, color=black];\n\t1321 -> 1470 [penwidth=1, color=black];\n\t1325 -> 1326 [penwidth=1, color=black];\n\t1326 -> 1275 [penwidth=1, color=black];\n\t1326 -> 1276 [penwidth=1, color=black];\n\t1326 -> 1373 [penwidth=\"1.6931471805599454\", color=black];\n\t1327 -> 1326 [penwidth=1, color=black];\n\t1328 -> 1229 [penwidth=1, color=black];\n\t1328 -> 1230 [penwidth=1, color=black];\n\t1328 -> 1232 [penwidth=1, color=black];\n\t1328 -> 1234 [penwidth=1, color=black];\n\t1329 -> 1236 [penwidth=1, color=black];\n\t1329 -> 1237 [penwidth=1, color=black];\n\t1329 -> 1238 [penwidth=1, color=black];\n\t1329 -> 1239 [penwidth=1, color=black];\n\t1329 -> 1240 [penwidth=1, color=black];\n\t1329 -> 1241 [penwidth=1, color=black];\n\t1329 -> 1242 [penwidth=1, color=black];\n\t1329 -> 1243 [penwidth=1, color=black];\n\t1329 -> 1244 [penwidth=1, color=black];\n\t1329 -> 1248 [penwidth=1, color=black];\n\t1329 -> 1249 [penwidth=1, color=black];\n\t1329 -> 1251 [penwidth=1, color=black];\n\t1329 -> 1252 [penwidth=1, color=black];\n\t1329 -> 1258 [penwidth=1, color=black];\n\t1329 -> 1259 [penwidth=1, color=black];\n\t1329 -> 1261 [penwidth=1, color=black];\n\t1329 -> 1262 [penwidth=1, color=black];\n\t1329 -> 1264 [penwidth=1, color=black];\n\t1329 -> 1267 [penwidth=1, color=black];\n\t1329 -> 1269 [penwidth=1, color=black];\n\t1329 -> 1270 [penwidth=1, color=black];\n\t1329 -> 1271 [penwidth=1, color=black];\n\t1329 -> 1272 [penwidth=\"2.791759469228055\", color=black];\n\t1329 -> 1315 [penwidth=1, color=black];\n\t1329 -> 1318 [penwidth=\"3.70805020110221\", color=black];\n\t1329 -> 1319 [penwidth=\"2.9459101490553135\", color=black];\n\t1329 -> 1363 [penwidth=1, color=black];\n\t1330 -> 1254 [penwidth=1, color=black];\n\t1330 -> 1255 [penwidth=1, color=black];\n\t1330 -> 1316 [penwidth=\"1.6931471805599454\", color=black];\n\t1331 -> 1253 [penwidth=1, color=black];\n\t1331 -> 1317 [penwidth=1, color=black];\n\t1332 -> 1266 [penwidth=1, color=black];\n\t1332 -> 1268 [penwidth=1, color=black];\n\t1333 -> 1260 [penwidth=1, color=black];\n\t1333 -> 1321 [penwidth=1, color=black];\n\t1334 -> 1245 [penwidth=1, color=black];\n\t1334 -> 1246 [penwidth=1, color=black];\n\t1334 -> 1247 [penwidth=1, color=black];\n\t1334 -> 1256 [penwidth=1, color=black];\n\t1334 -> 1263 [penwidth=1, color=black];\n\t1335 -> 1320 [penwidth=1, color=black];\n\t1335 -> 1321 [penwidth=1, color=black];\n\t1335 -> 1322 [penwidth=1, color=black];\n\t1335 -> 1323 [penwidth=1, color=black];\n\t1335 -> 1324 [penwidth=1, color=black];\n\t1336 -> 1250 [penwidth=1, color=black];\n\t1336 -> 1257 [penwidth=1, color=black];\n\t1336 -> 1265 [penwidth=1, color=black];\n\t1336 -> 1274 [penwidth=1, color=black];\n\t1336 -> 1317 [penwidth=1, color=black];\n\t1336 -> 1320 [penwidth=1, color=black];\n\t1337 -> 1228 [penwidth=1, color=black];\n\t1337 -> 1231 [penwidth=1, color=black];\n\t1337 -> 1235 [penwidth=1, color=black];\n\t1355 -> 1343 [penwidth=1, color=black];\n\t1355 -> 1345 [penwidth=1, color=black];\n\t1355 -> 1356 [penwidth=1, color=black];\n\t1355 -> 1363 [penwidth=1, color=black];\n\t1356 -> 1342 [penwidth=1, color=black];\n\t1356 -> 1344 [penwidth=1, color=black];\n\t1356 -> 1346 [penwidth=1, color=black];\n\t1356 -> 1347 [penwidth=1, color=black];\n\t1356 -> 1348 [penwidth=1, color=black];\n\t1356 -> 1349 [penwidth=1, color=black];\n\t1356 -> 1351 [penwidth=1, color=black];\n\t1356 -> 1352 [penwidth=1, color=black];\n\t1356 -> 1353 [penwidth=1, color=black];\n\t1356 -> 1354 [penwidth=1, color=black];\n\t1357 -> 1369 [penwidth=1, color=black];\n\t1357 -> 1429 [penwidth=1, color=black];\n\t1358 -> 1355 [penwidth=1, color=black];\n\t1358 -> 1369 [penwidth=1, color=black];\n\t1358 -> 1429 [penwidth=1, color=black];\n\t1359 -> 1345 [penwidth=1, color=black];\n\t1359 -> 1373 [penwidth=1, color=black];\n\t1359 -> 1387 [penwidth=\"2.09861228866811\", color=black];\n\t1360 -> 1342 [penwidth=1, color=black];\n\t1360 -> 1344 [penwidth=1, color=black];\n\t1360 -> 1346 [penwidth=1, color=black];\n\t1360 -> 1347 [penwidth=1, color=black];\n\t1360 -> 1348 [penwidth=1, color=black];\n\t1360 -> 1349 [penwidth=1, color=black];\n\t1360 -> 1351 [penwidth=1, color=black];\n\t1360 -> 1352 [penwidth=1, color=black];\n\t1360 -> 1353 [penwidth=1, color=black];\n\t1360 -> 1354 [penwidth=1, color=black];\n\t1360 -> 1435 [penwidth=\"3.302585092994046\", color=black];\n\t1361 -> 1350 [penwidth=1, color=black];\n\t1361 -> 1396 [penwidth=1, color=black];\n\t1362 -> 1345 [penwidth=1, color=black];\n\t1362 -> 1355 [penwidth=1, color=black];\n\t1362 -> 1373 [penwidth=1, color=black];\n\t1364 -> 1363 [penwidth=1, color=black];\n\t1365 -> 1345 [penwidth=\"1.6931471805599454\", color=black];\n\t1366 -> 1342 [penwidth=1, color=black];\n\t1366 -> 1344 [penwidth=1, color=black];\n\t1366 -> 1346 [penwidth=1, color=black];\n\t1366 -> 1347 [penwidth=1, color=black];\n\t1366 -> 1348 [penwidth=1, color=black];\n\t1366 -> 1349 [penwidth=1, color=black];\n\t1366 -> 1351 [penwidth=1, color=black];\n\t1366 -> 1352 [penwidth=1, color=black];\n\t1366 -> 1353 [penwidth=1, color=black];\n\t1366 -> 1354 [penwidth=1, color=black];\n\t1367 -> 1363 [penwidth=1, color=black];\n\t1368 -> 1343 [penwidth=1, color=black];\n\t1368 -> 1345 [penwidth=1, color=black];\n\t1369 -> 1350 [penwidth=1, color=black];\n\t1369 -> 1431 [penwidth=1, color=black];\n\t1370 -> 1371 [penwidth=1, color=black];\n\t1370 -> 1379 [penwidth=1, color=black];\n\t1370 -> 1440 [penwidth=1, color=black];\n\t1371 -> 1378 [penwidth=1, color=black];\n\t1371 -> 1380 [penwidth=1, color=black];\n\t1371 -> 1441 [penwidth=1, color=black];\n\t1372 -> 1378 [penwidth=1, color=black];\n\t1374 -> 1375 [penwidth=1, color=black];\n\t1374 -> 1387 [penwidth=\"1.6931471805599454\", color=black];\n\t1375 -> 1394 [penwidth=1, color=black];\n\t1375 -> 1441 [penwidth=\"1.6931471805599454\", color=black];\n\t1376 -> 1375 [penwidth=1, color=black];\n\t1376 -> 1416 [penwidth=\"1.6931471805599454\", color=black];\n\t1377 -> 1381 [penwidth=1, color=black];\n\t1379 -> 1433 [penwidth=1, color=black];\n\t1380 -> 1379 [penwidth=1, color=black];\n\t1380 -> 1441 [penwidth=1, color=black];\n\t1382 -> 1406 [penwidth=1, color=black];\n\t1382 -> 1415 [penwidth=1, color=black];\n\t1383 -> 1435 [penwidth=\"1.6931471805599454\", color=black];\n\t1384 -> 1429 [penwidth=1, color=black];\n\t1385 -> 1384 [penwidth=1, color=black];\n\t1385 -> 1433 [penwidth=1, color=black];\n\t1386 -> 1428 [penwidth=1, color=black];\n\t1386 -> 1435 [penwidth=1, color=black];\n\t1388 -> 1384 [penwidth=1, color=black];\n\t1389 -> 1429 [penwidth=1, color=black];\n\t1389 -> 1882 [penwidth=1, color=black];\n\t1391 -> 1371 [penwidth=1, color=black];\n\t1391 -> 1378 [penwidth=1, color=black];\n\t1392 -> 1372 [penwidth=1, color=black];\n\t1392 -> 1373 [penwidth=\"1.6931471805599454\", color=black];\n\t1393 -> 1372 [penwidth=1, color=black];\n\t1393 -> 1373 [penwidth=\"1.6931471805599454\", color=black];\n\t1394 -> 1373 [penwidth=1, color=black];\n\t1395 -> 1373 [penwidth=1, color=black];\n\t1395 -> 1442 [penwidth=1, color=black];\n\t1396 -> 1373 [penwidth=\"1.6931471805599454\", color=black];\n\t1396 -> 1428 [penwidth=1, color=black];\n\t1397 -> 1387 [penwidth=1, color=black];\n\t1397 -> 1395 [penwidth=1, color=black];\n\t1397 -> 1433 [penwidth=1, color=black];\n\t1398 -> 1399 [penwidth=1, color=black];\n\t1399 -> 1397 [penwidth=1, color=black];\n\t1399 -> 1433 [penwidth=1, color=black];\n\t1399 -> 1871 [penwidth=1, color=black];\n\t1399 -> 1882 [penwidth=1, color=black];\n\t1400 -> 1397 [penwidth=1, color=black];\n\t1401 -> 1398 [penwidth=1, color=black];\n\t1402 -> 1399 [penwidth=1, color=black];\n\t1403 -> 1373 [penwidth=\"2.09861228866811\", color=black];\n\t1403 -> 1405 [penwidth=\"1.6931471805599454\", color=black];\n\t1403 -> 1406 [penwidth=1, color=black];\n\t1403 -> 1432 [penwidth=1, color=black];\n\t1404 -> 1403 [penwidth=1, color=black];\n\t1404 -> 1405 [penwidth=1, color=black];\n\t1404 -> 1414 [penwidth=1, color=black];\n\t1406 -> 1405 [penwidth=1, color=black];\n\t1406 -> 1414 [penwidth=1, color=black];\n\t1407 -> 1387 [penwidth=1, color=black];\n\t1408 -> 1387 [penwidth=1, color=black];\n\t1408 -> 1432 [penwidth=1, color=black];\n\t1410 -> 1429 [penwidth=1, color=black];\n\t1411 -> 1429 [penwidth=1, color=black];\n\t1411 -> 1430 [penwidth=1, color=black];\n\t1411 -> 1431 [penwidth=1, color=black];\n\t1412 -> 1429 [penwidth=1, color=black];\n\t1413 -> 1373 [penwidth=1, color=black];\n\t1413 -> 1428 [penwidth=1, color=black];\n\t1414 -> 1373 [penwidth=1, color=black];\n\t1415 -> 1403 [penwidth=1, color=black];\n\t1415 -> 1414 [penwidth=1, color=black];\n\t1417 -> 1383 [penwidth=1, color=black];\n\t1417 -> 1406 [penwidth=1, color=black];\n\t1418 -> 1428 [penwidth=1, color=black];\n\t1419 -> 1404 [penwidth=1, color=chartreuse];\n\t1420 -> 1406 [penwidth=1, color=black];\n\t1421 -> 1405 [penwidth=1, color=black];\n\t1422 -> 1405 [penwidth=1, color=black];\n\t1425 -> 1370 [penwidth=1, color=black];\n\t1425 -> 1371 [penwidth=1, color=black];\n\t1425 -> 1373 [penwidth=\"1.6931471805599454\", color=black];\n\t1425 -> 1391 [penwidth=1, color=black];\n\t1425 -> 1394 [penwidth=1, color=black];\n\t1425 -> 1442 [penwidth=1, color=black];\n\t1426 -> 1430 [penwidth=1, color=black];\n\t1427 -> 1373 [penwidth=1, color=black];\n\t1429 -> 1372 [penwidth=1, color=black];\n\t1429 -> 1413 [penwidth=\"1.6931471805599454\", color=black];\n\t1430 -> 1396 [penwidth=1, color=black];\n\t1431 -> 1382 [penwidth=1, color=black];\n\t1431 -> 1434 [penwidth=1, color=black];\n\t1432 -> 1371 [penwidth=1, color=black];\n\t1432 -> 1378 [penwidth=1, color=black];\n\t1433 -> 1373 [penwidth=1, color=black];\n\t1434 -> 1874 [penwidth=1, color=black];\n\t1434 -> 1882 [penwidth=1, color=black];\n\t1435 -> 1436 [penwidth=1, color=black];\n\t1436 -> 1433 [penwidth=1, color=black];\n\t1437 -> 1433 [penwidth=1, color=black];\n\t1438 -> 1387 [penwidth=1, color=black];\n\t1438 -> 1439 [penwidth=1, color=black];\n\t1442 -> 1371 [penwidth=\"1.6931471805599454\", color=black];\n\t1442 -> 1372 [penwidth=1, color=black];\n\t1443 -> 1370 [penwidth=1, color=black];\n\t1443 -> 1373 [penwidth=1, color=black];\n\t1443 -> 1428 [penwidth=\"2.09861228866811\", color=black];\n\t1443 -> 1429 [penwidth=1, color=black];\n\t1443 -> 1433 [penwidth=1, color=black];\n\t1443 -> 1449 [penwidth=1, color=black];\n\t1443 -> 1450 [penwidth=1, color=black];\n\t1444 -> 1392 [penwidth=1, color=black];\n\t1444 -> 1444 [penwidth=1, color=black];\n\t1445 -> 1377 [penwidth=1, color=black];\n\t1445 -> 1433 [penwidth=1, color=black];\n\t1446 -> 1372 [penwidth=1, color=black];\n\t1446 -> 1373 [penwidth=1, color=black];\n\t1446 -> 1433 [penwidth=\"1.6931471805599454\", color=black];\n\t1447 -> 1443 [penwidth=1, color=black];\n\t1447 -> 1444 [penwidth=1, color=black];\n\t1447 -> 1450 [penwidth=1, color=black];\n\t1448 -> 1373 [penwidth=1, color=black];\n\t1448 -> 1377 [penwidth=1, color=black];\n\t1448 -> 1379 [penwidth=1, color=black];\n\t1449 -> 1373 [penwidth=1, color=black];\n\t1449 -> 1379 [penwidth=1, color=black];\n\t1450 -> 1445 [penwidth=1, color=black];\n\t1450 -> 1446 [penwidth=1, color=black];\n\t1450 -> 1448 [penwidth=1, color=black];\n\t1450 -> 1449 [penwidth=1, color=black];\n\t1451 -> 1432 [penwidth=1, color=black];\n\t1451 -> 1447 [penwidth=1, color=black];\n\t1453 -> 1462 [penwidth=1, color=black];\n\t1453 -> 1871 [penwidth=1, color=black];\n\t1454 -> 1457 [penwidth=1, color=black];\n\t1454 -> 1468 [penwidth=1, color=black];\n\t1454 -> 1489 [penwidth=1, color=black];\n\t1455 -> 1475 [penwidth=\"1.6931471805599454\", color=black];\n\t1460 -> 1467 [penwidth=1, color=chartreuse];\n\t1462 -> 1876 [penwidth=1, color=black];\n\t1462 -> 1878 [penwidth=1, color=black];\n\t1462 -> 1879 [penwidth=1, color=black];\n\t1463 -> 1452 [penwidth=1, color=black];\n\t1463 -> 1453 [penwidth=1, color=black];\n\t1464 -> 1470 [penwidth=1, color=black];\n\t1465 -> 1469 [penwidth=1, color=black];\n\t1465 -> 1470 [penwidth=1, color=black];\n\t1466 -> 1882 [penwidth=1, color=black];\n\t1467 -> 1463 [penwidth=1, color=black];\n\t1472 -> 1466 [penwidth=1, color=chartreuse];\n\t1483 -> 1452 [penwidth=1, color=black];\n\t1486 -> 1488 [penwidth=1, color=chartreuse];\n\t1488 -> 1483 [penwidth=1, color=black];\n\t1492 -> 1502 [penwidth=1, color=black];\n\t1492 -> 1503 [penwidth=1, color=black];\n\t1492 -> 1504 [penwidth=1, color=black];\n\t1492 -> 1505 [penwidth=1, color=black];\n\t1492 -> 1506 [penwidth=1, color=black];\n\t1492 -> 1507 [penwidth=1, color=black];\n\t1492 -> 1508 [penwidth=1, color=black];\n\t1492 -> 1509 [penwidth=1, color=black];\n\t1492 -> 1510 [penwidth=1, color=black];\n\t1492 -> 1511 [penwidth=1, color=black];\n\t1492 -> 1512 [penwidth=1, color=black];\n\t1492 -> 1514 [penwidth=1, color=black];\n\t1492 -> 1515 [penwidth=1, color=black];\n\t1492 -> 1516 [penwidth=1, color=black];\n\t1492 -> 1517 [penwidth=1, color=black];\n\t1497 -> 1491 [penwidth=1, color=black];\n\t1497 -> 1499 [penwidth=1, color=black];\n\t1497 -> 1500 [penwidth=1, color=black];\n\t1498 -> 1491 [penwidth=\"2.386294361119891\", color=black];\n\t1498 -> 1493 [penwidth=1, color=black];\n\t1498 -> 1494 [penwidth=1, color=black];\n\t1498 -> 1496 [penwidth=1, color=black];\n\t1498 -> 1501 [penwidth=1, color=black];\n\t1499 -> 1498 [penwidth=1, color=black];\n\t1499 -> 1500 [penwidth=1, color=black];\n\t1500 -> 1491 [penwidth=1, color=black];\n\t1502 -> 1490 [penwidth=1, color=black];\n\t1502 -> 1493 [penwidth=1, color=black];\n\t1502 -> 1495 [penwidth=1, color=black];\n\t1502 -> 1496 [penwidth=1, color=black];\n\t1502 -> 1501 [penwidth=1, color=black];\n\t1503 -> 1490 [penwidth=1, color=black];\n\t1503 -> 1493 [penwidth=1, color=black];\n\t1503 -> 1495 [penwidth=1, color=black];\n\t1503 -> 1496 [penwidth=1, color=black];\n\t1503 -> 1501 [penwidth=1, color=black];\n\t1504 -> 1490 [penwidth=1, color=black];\n\t1504 -> 1493 [penwidth=1, color=black];\n\t1504 -> 1495 [penwidth=1, color=black];\n\t1504 -> 1496 [penwidth=1, color=black];\n\t1504 -> 1501 [penwidth=1, color=black];\n\t1505 -> 1490 [penwidth=1, color=black];\n\t1505 -> 1493 [penwidth=1, color=black];\n\t1505 -> 1495 [penwidth=1, color=black];\n\t1505 -> 1496 [penwidth=1, color=black];\n\t1505 -> 1501 [penwidth=1, color=black];\n\t1506 -> 1490 [penwidth=1, color=black];\n\t1506 -> 1493 [penwidth=1, color=black];\n\t1506 -> 1495 [penwidth=1, color=black];\n\t1506 -> 1496 [penwidth=1, color=black];\n\t1506 -> 1501 [penwidth=1, color=black];\n\t1507 -> 1490 [penwidth=1, color=black];\n\t1507 -> 1493 [penwidth=1, color=black];\n\t1507 -> 1495 [penwidth=1, color=black];\n\t1507 -> 1496 [penwidth=1, color=black];\n\t1507 -> 1501 [penwidth=1, color=black];\n\t1508 -> 1490 [penwidth=1, color=black];\n\t1508 -> 1493 [penwidth=1, color=black];\n\t1508 -> 1495 [penwidth=1, color=black];\n\t1508 -> 1496 [penwidth=1, color=black];\n\t1508 -> 1501 [penwidth=1, color=black];\n\t1509 -> 1490 [penwidth=1, color=black];\n\t1509 -> 1493 [penwidth=1, color=black];\n\t1509 -> 1495 [penwidth=1, color=black];\n\t1509 -> 1496 [penwidth=1, color=black];\n\t1509 -> 1501 [penwidth=1, color=black];\n\t1510 -> 1490 [penwidth=1, color=black];\n\t1510 -> 1493 [penwidth=1, color=black];\n\t1510 -> 1495 [penwidth=1, color=black];\n\t1510 -> 1496 [penwidth=1, color=black];\n\t1510 -> 1501 [penwidth=1, color=black];\n\t1511 -> 1490 [penwidth=1, color=black];\n\t1511 -> 1493 [penwidth=1, color=black];\n\t1511 -> 1495 [penwidth=1, color=black];\n\t1511 -> 1496 [penwidth=1, color=black];\n\t1511 -> 1501 [penwidth=1, color=black];\n\t1512 -> 1490 [penwidth=1, color=black];\n\t1512 -> 1493 [penwidth=1, color=black];\n\t1512 -> 1495 [penwidth=1, color=black];\n\t1512 -> 1496 [penwidth=1, color=black];\n\t1512 -> 1501 [penwidth=1, color=black];\n\t1513 -> 1490 [penwidth=1, color=black];\n\t1513 -> 1493 [penwidth=1, color=black];\n\t1513 -> 1495 [penwidth=1, color=black];\n\t1513 -> 1496 [penwidth=1, color=black];\n\t1513 -> 1501 [penwidth=1, color=black];\n\t1514 -> 1490 [penwidth=1, color=black];\n\t1514 -> 1493 [penwidth=1, color=black];\n\t1514 -> 1495 [penwidth=1, color=black];\n\t1514 -> 1496 [penwidth=1, color=black];\n\t1514 -> 1501 [penwidth=1, color=black];\n\t1515 -> 1490 [penwidth=1, color=black];\n\t1515 -> 1493 [penwidth=1, color=black];\n\t1515 -> 1495 [penwidth=1, color=black];\n\t1515 -> 1496 [penwidth=1, color=black];\n\t1515 -> 1501 [penwidth=1, color=black];\n\t1516 -> 1490 [penwidth=1, color=black];\n\t1516 -> 1493 [penwidth=1, color=black];\n\t1516 -> 1495 [penwidth=1, color=black];\n\t1516 -> 1496 [penwidth=1, color=black];\n\t1516 -> 1501 [penwidth=1, color=black];\n\t1517 -> 1490 [penwidth=1, color=black];\n\t1517 -> 1493 [penwidth=1, color=black];\n\t1517 -> 1495 [penwidth=1, color=black];\n\t1517 -> 1496 [penwidth=1, color=black];\n\t1517 -> 1501 [penwidth=1, color=black];\n\t1519 -> 1889 [penwidth=\"2.386294361119891\", color=black];\n\t1520 -> 152 [penwidth=1, color=black];\n\t1520 -> 161 [penwidth=1, color=black];\n\t1520 -> 225 [penwidth=1, color=black];\n\t1520 -> 304 [penwidth=1, color=black];\n\t1520 -> 1520 [penwidth=1, color=black];\n\t1520 -> 1528 [penwidth=\"1.6931471805599454\", color=black];\n\t1520 -> 1871 [penwidth=1, color=black];\n\t1520 -> 1889 [penwidth=\"1.6931471805599454\", color=black];\n\t1521 -> 1527 [penwidth=1, color=black];\n\t1521 -> 1778 [penwidth=1, color=black];\n\t1522 -> 1266 [penwidth=1, color=black];\n\t1522 -> 1268 [penwidth=1, color=black];\n\t1522 -> 1524 [penwidth=1, color=black];\n\t1522 -> 1889 [penwidth=1, color=black];\n\t1523 -> 1250 [penwidth=1, color=black];\n\t1523 -> 1257 [penwidth=1, color=black];\n\t1523 -> 1265 [penwidth=1, color=black];\n\t1523 -> 1524 [penwidth=1, color=orange];\n\t1523 -> 1528 [penwidth=1, color=black];\n\t1523 -> 1889 [penwidth=\"1.6931471805599454\", color=black];\n\t1524 -> 1523 [penwidth=1, color=orange];\n\t1524 -> 1661 [penwidth=1, color=chartreuse];\n\t1525 -> 1606 [penwidth=1, color=black];\n\t1526 -> 431 [penwidth=1, color=black];\n\t1526 -> 1528 [penwidth=1, color=black];\n\t1527 -> 1889 [penwidth=1, color=black];\n\t1528 -> 1606 [penwidth=1, color=black];\n\t1529 -> 1528 [penwidth=1, color=black];\n\t1533 -> 1519 [penwidth=1, color=black];\n\t1534 -> 1519 [penwidth=1, color=black];\n\t1535 -> 1602 [penwidth=1, color=black];\n\t1535 -> 1776 [penwidth=1, color=black];\n\t1536 -> 1773 [penwidth=1, color=black];\n\t1536 -> 1774 [penwidth=1, color=black];\n\t1536 -> 1775 [penwidth=1, color=black];\n\t1536 -> 1778 [penwidth=1, color=black];\n\t1537 -> 1521 [penwidth=1, color=black];\n\t1537 -> 1777 [penwidth=1, color=black];\n\t1538 -> 1518 [penwidth=1, color=black];\n\t1539 -> 84 [penwidth=1, color=black];\n\t1540 -> 1518 [penwidth=1, color=black];\n\t1541 -> 1518 [penwidth=1, color=black];\n\t1542 -> 82 [penwidth=1, color=black];\n\t1542 -> 1527 [penwidth=1, color=black];\n\t1543 -> 316 [penwidth=1, color=black];\n\t1543 -> 317 [penwidth=1, color=black];\n\t1543 -> 1612 [penwidth=1, color=black];\n\t1544 -> 85 [penwidth=1, color=black];\n\t1544 -> 86 [penwidth=1, color=black];\n\t1544 -> 87 [penwidth=1, color=black];\n\t1544 -> 88 [penwidth=1, color=black];\n\t1544 -> 93 [penwidth=1, color=black];\n\t1544 -> 94 [penwidth=1, color=black];\n\t1544 -> 104 [penwidth=1, color=black];\n\t1544 -> 105 [penwidth=1, color=black];\n\t1544 -> 108 [penwidth=1, color=black];\n\t1544 -> 109 [penwidth=1, color=black];\n\t1544 -> 110 [penwidth=1, color=black];\n\t1544 -> 111 [penwidth=1, color=black];\n\t1544 -> 113 [penwidth=1, color=black];\n\t1544 -> 117 [penwidth=1, color=black];\n\t1544 -> 118 [penwidth=1, color=black];\n\t1544 -> 121 [penwidth=1, color=black];\n\t1544 -> 123 [penwidth=1, color=black];\n\t1544 -> 125 [penwidth=1, color=black];\n\t1544 -> 126 [penwidth=1, color=black];\n\t1544 -> 130 [penwidth=1, color=black];\n\t1544 -> 131 [penwidth=1, color=black];\n\t1544 -> 132 [penwidth=1, color=black];\n\t1544 -> 133 [penwidth=1, color=black];\n\t1544 -> 134 [penwidth=1, color=black];\n\t1544 -> 141 [penwidth=1, color=black];\n\t1544 -> 143 [penwidth=1, color=black];\n\t1544 -> 144 [penwidth=1, color=black];\n\t1544 -> 145 [penwidth=1, color=black];\n\t1544 -> 149 [penwidth=1, color=black];\n\t1544 -> 154 [penwidth=1, color=black];\n\t1544 -> 160 [penwidth=1, color=black];\n\t1544 -> 163 [penwidth=1, color=black];\n\t1544 -> 164 [penwidth=1, color=black];\n\t1544 -> 165 [penwidth=1, color=black];\n\t1544 -> 166 [penwidth=1, color=black];\n\t1544 -> 167 [penwidth=1, color=black];\n\t1544 -> 175 [penwidth=1, color=black];\n\t1544 -> 176 [penwidth=1, color=black];\n\t1544 -> 177 [penwidth=1, color=black];\n\t1544 -> 178 [penwidth=1, color=black];\n\t1544 -> 179 [penwidth=1, color=black];\n\t1544 -> 180 [penwidth=1, color=black];\n\t1544 -> 181 [penwidth=1, color=black];\n\t1544 -> 182 [penwidth=1, color=black];\n\t1544 -> 188 [penwidth=1, color=black];\n\t1544 -> 189 [penwidth=1, color=black];\n\t1544 -> 190 [penwidth=1, color=black];\n\t1544 -> 202 [penwidth=1, color=black];\n\t1544 -> 205 [penwidth=1, color=black];\n\t1544 -> 207 [penwidth=1, color=black];\n\t1544 -> 212 [penwidth=1, color=black];\n\t1544 -> 213 [penwidth=1, color=black];\n\t1544 -> 214 [penwidth=1, color=black];\n\t1544 -> 215 [penwidth=1, color=black];\n\t1544 -> 216 [penwidth=1, color=black];\n\t1544 -> 217 [penwidth=1, color=black];\n\t1544 -> 218 [penwidth=1, color=black];\n\t1544 -> 219 [penwidth=1, color=black];\n\t1544 -> 220 [penwidth=1, color=black];\n\t1544 -> 221 [penwidth=1, color=black];\n\t1544 -> 222 [penwidth=1, color=black];\n\t1544 -> 223 [penwidth=1, color=black];\n\t1544 -> 224 [penwidth=1, color=black];\n\t1544 -> 226 [penwidth=1, color=black];\n\t1544 -> 227 [penwidth=1, color=black];\n\t1544 -> 228 [penwidth=1, color=black];\n\t1544 -> 229 [penwidth=1, color=black];\n\t1544 -> 230 [penwidth=1, color=black];\n\t1544 -> 233 [penwidth=1, color=black];\n\t1544 -> 234 [penwidth=1, color=black];\n\t1544 -> 235 [penwidth=1, color=black];\n\t1544 -> 239 [penwidth=1, color=black];\n\t1544 -> 245 [penwidth=1, color=black];\n\t1544 -> 246 [penwidth=1, color=black];\n\t1544 -> 248 [penwidth=1, color=black];\n\t1544 -> 249 [penwidth=1, color=black];\n\t1544 -> 251 [penwidth=1, color=black];\n\t1544 -> 252 [penwidth=1, color=black];\n\t1544 -> 253 [penwidth=1, color=black];\n\t1544 -> 259 [penwidth=1, color=black];\n\t1544 -> 265 [penwidth=1, color=black];\n\t1544 -> 269 [penwidth=1, color=black];\n\t1544 -> 272 [penwidth=1, color=black];\n\t1544 -> 273 [penwidth=1, color=black];\n\t1544 -> 276 [penwidth=1, color=black];\n\t1544 -> 277 [penwidth=1, color=black];\n\t1544 -> 278 [penwidth=1, color=black];\n\t1544 -> 279 [penwidth=1, color=black];\n\t1544 -> 280 [penwidth=1, color=black];\n\t1544 -> 282 [penwidth=1, color=black];\n\t1544 -> 287 [penwidth=1, color=black];\n\t1544 -> 289 [penwidth=1, color=black];\n\t1544 -> 290 [penwidth=1, color=black];\n\t1544 -> 291 [penwidth=1, color=black];\n\t1544 -> 293 [penwidth=1, color=black];\n\t1544 -> 294 [penwidth=1, color=black];\n\t1544 -> 296 [penwidth=1, color=black];\n\t1544 -> 297 [penwidth=1, color=black];\n\t1544 -> 305 [penwidth=1, color=black];\n\t1544 -> 308 [penwidth=1, color=black];\n\t1544 -> 309 [penwidth=1, color=black];\n\t1544 -> 312 [penwidth=1, color=black];\n\t1544 -> 313 [penwidth=1, color=black];\n\t1544 -> 314 [penwidth=1, color=black];\n\t1544 -> 315 [penwidth=1, color=black];\n\t1544 -> 319 [penwidth=1, color=black];\n\t1544 -> 323 [penwidth=1, color=black];\n\t1544 -> 324 [penwidth=1, color=black];\n\t1544 -> 327 [penwidth=1, color=black];\n\t1544 -> 329 [penwidth=1, color=black];\n\t1544 -> 330 [penwidth=1, color=black];\n\t1544 -> 334 [penwidth=1, color=black];\n\t1544 -> 336 [penwidth=1, color=black];\n\t1544 -> 337 [penwidth=1, color=black];\n\t1544 -> 340 [penwidth=1, color=black];\n\t1544 -> 342 [penwidth=1, color=black];\n\t1544 -> 344 [penwidth=1, color=black];\n\t1544 -> 345 [penwidth=1, color=black];\n\t1544 -> 347 [penwidth=1, color=black];\n\t1544 -> 348 [penwidth=1, color=black];\n\t1544 -> 350 [penwidth=1, color=black];\n\t1544 -> 351 [penwidth=1, color=black];\n\t1544 -> 352 [penwidth=1, color=black];\n\t1544 -> 354 [penwidth=1, color=black];\n\t1544 -> 359 [penwidth=1, color=black];\n\t1544 -> 361 [penwidth=1, color=black];\n\t1544 -> 366 [penwidth=1, color=black];\n\t1544 -> 367 [penwidth=1, color=black];\n\t1544 -> 370 [penwidth=1, color=black];\n\t1544 -> 371 [penwidth=1, color=black];\n\t1544 -> 372 [penwidth=1, color=black];\n\t1544 -> 373 [penwidth=1, color=black];\n\t1544 -> 374 [penwidth=1, color=black];\n\t1544 -> 375 [penwidth=1, color=black];\n\t1544 -> 376 [penwidth=1, color=black];\n\t1544 -> 379 [penwidth=1, color=black];\n\t1544 -> 385 [penwidth=1, color=black];\n\t1544 -> 386 [penwidth=1, color=black];\n\t1544 -> 388 [penwidth=1, color=black];\n\t1544 -> 394 [penwidth=1, color=black];\n\t1544 -> 395 [penwidth=1, color=black];\n\t1544 -> 396 [penwidth=1, color=black];\n\t1544 -> 398 [penwidth=1, color=black];\n\t1544 -> 399 [penwidth=1, color=black];\n\t1544 -> 401 [penwidth=1, color=black];\n\t1544 -> 1525 [penwidth=1, color=black];\n\t1544 -> 1527 [penwidth=\"2.386294361119891\", color=black];\n\t1544 -> 1528 [penwidth=\"4.49650756146648\", color=black];\n\t1544 -> 1664 [penwidth=1, color=black];\n\t1545 -> 1518 [penwidth=1, color=black];\n\t1546 -> 1518 [penwidth=1, color=black];\n\t1547 -> 644 [penwidth=1, color=black];\n\t1547 -> 873 [penwidth=1, color=black];\n\t1547 -> 1074 [penwidth=1, color=black];\n\t1547 -> 1075 [penwidth=1, color=black];\n\t1547 -> 1188 [penwidth=1, color=black];\n\t1548 -> 645 [penwidth=1, color=black];\n\t1548 -> 1187 [penwidth=1, color=black];\n\t1549 -> 1518 [penwidth=1, color=black];\n\t1550 -> 1518 [penwidth=1, color=black];\n\t1551 -> 122 [penwidth=1, color=black];\n\t1551 -> 281 [penwidth=1, color=black];\n\t1551 -> 1611 [penwidth=1, color=black];\n\t1552 -> 1518 [penwidth=1, color=black];\n\t1553 -> 1518 [penwidth=1, color=black];\n\t1554 -> 263 [penwidth=1, color=black];\n\t1554 -> 400 [penwidth=1, color=black];\n\t1554 -> 1528 [penwidth=1, color=black];\n\t1555 -> 1527 [penwidth=\"2.09861228866811\", color=black];\n\t1556 -> 1528 [penwidth=1, color=black];\n\t1556 -> 1608 [penwidth=1, color=black];\n\t1557 -> 1518 [penwidth=1, color=black];\n\t1558 -> 1236 [penwidth=1, color=black];\n\t1558 -> 1237 [penwidth=1, color=black];\n\t1558 -> 1238 [penwidth=1, color=black];\n\t1558 -> 1239 [penwidth=1, color=black];\n\t1558 -> 1240 [penwidth=1, color=black];\n\t1558 -> 1241 [penwidth=1, color=black];\n\t1558 -> 1242 [penwidth=1, color=black];\n\t1558 -> 1243 [penwidth=1, color=black];\n\t1558 -> 1244 [penwidth=1, color=black];\n\t1558 -> 1248 [penwidth=1, color=black];\n\t1558 -> 1249 [penwidth=1, color=black];\n\t1558 -> 1251 [penwidth=1, color=black];\n\t1558 -> 1252 [penwidth=1, color=black];\n\t1558 -> 1258 [penwidth=1, color=black];\n\t1558 -> 1259 [penwidth=1, color=black];\n\t1558 -> 1261 [penwidth=1, color=black];\n\t1558 -> 1262 [penwidth=1, color=black];\n\t1558 -> 1264 [penwidth=1, color=black];\n\t1558 -> 1267 [penwidth=1, color=black];\n\t1558 -> 1269 [penwidth=1, color=black];\n\t1558 -> 1270 [penwidth=1, color=black];\n\t1558 -> 1271 [penwidth=1, color=black];\n\t1558 -> 1528 [penwidth=\"2.6094379124341005\", color=black];\n\t1559 -> 1254 [penwidth=1, color=black];\n\t1559 -> 1255 [penwidth=1, color=black];\n\t1559 -> 1522 [penwidth=1, color=black];\n\t1560 -> 1253 [penwidth=1, color=black];\n\t1561 -> 1522 [penwidth=1, color=black];\n\t1562 -> 1260 [penwidth=1, color=black];\n\t1562 -> 1527 [penwidth=1, color=black];\n\t1563 -> 1518 [penwidth=1, color=black];\n\t1564 -> 1233 [penwidth=1, color=black];\n\t1564 -> 1527 [penwidth=1, color=black];\n\t1565 -> 1523 [penwidth=1, color=chartreuse];\n\t1566 -> 1518 [penwidth=1, color=black];\n\t1567 -> 1518 [penwidth=1, color=black];\n\t1568 -> 187 [penwidth=1, color=black];\n\t1568 -> 321 [penwidth=1, color=black];\n\t1568 -> 365 [penwidth=1, color=black];\n\t1568 -> 1527 [penwidth=1, color=black];\n\t1568 -> 1528 [penwidth=1, color=black];\n\t1568 -> 1610 [penwidth=1, color=black];\n\t1569 -> 83 [penwidth=1, color=black];\n\t1569 -> 209 [penwidth=1, color=black];\n\t1569 -> 210 [penwidth=1, color=black];\n\t1569 -> 1526 [penwidth=1, color=black];\n\t1569 -> 1603 [penwidth=1, color=black];\n\t1570 -> 206 [penwidth=1, color=black];\n\t1570 -> 210 [penwidth=1, color=black];\n\t1571 -> 208 [penwidth=1, color=black];\n\t1571 -> 211 [penwidth=1, color=black];\n\t1572 -> 1518 [penwidth=1, color=black];\n\t1573 -> 1518 [penwidth=1, color=black];\n\t1574 -> 1518 [penwidth=1, color=black];\n\t1575 -> 115 [penwidth=1, color=black];\n\t1575 -> 197 [penwidth=1, color=black];\n\t1575 -> 204 [penwidth=1, color=black];\n\t1575 -> 307 [penwidth=1, color=black];\n\t1575 -> 326 [penwidth=1, color=black];\n\t1575 -> 338 [penwidth=1, color=black];\n\t1575 -> 339 [penwidth=1, color=black];\n\t1575 -> 397 [penwidth=1, color=black];\n\t1576 -> 135 [penwidth=1, color=black];\n\t1576 -> 136 [penwidth=1, color=black];\n\t1576 -> 286 [penwidth=1, color=black];\n\t1577 -> 283 [penwidth=1, color=black];\n\t1577 -> 284 [penwidth=1, color=black];\n\t1577 -> 285 [penwidth=1, color=black];\n\t1577 -> 288 [penwidth=1, color=black];\n\t1578 -> 1518 [penwidth=1, color=black];\n\t1579 -> 299 [penwidth=1, color=black];\n\t1579 -> 1612 [penwidth=\"2.09861228866811\", color=black];\n\t1580 -> 1528 [penwidth=1, color=black];\n\t1580 -> 1607 [penwidth=1, color=black];\n\t1582 -> 300 [penwidth=1, color=black];\n\t1582 -> 358 [penwidth=1, color=black];\n\t1582 -> 1527 [penwidth=1, color=black];\n\t1582 -> 1662 [penwidth=1, color=black];\n\t1583 -> 1518 [penwidth=1, color=black];\n\t1584 -> 1518 [penwidth=1, color=black];\n\t1585 -> 1518 [penwidth=1, color=black];\n\t1586 -> 89 [penwidth=1, color=black];\n\t1586 -> 90 [penwidth=1, color=black];\n\t1586 -> 116 [penwidth=1, color=black];\n\t1586 -> 150 [penwidth=1, color=black];\n\t1586 -> 156 [penwidth=1, color=black];\n\t1586 -> 1612 [penwidth=1, color=black];\n\t1587 -> 1520 [penwidth=1, color=chartreuse];\n\t1588 -> 322 [penwidth=1, color=black];\n\t1588 -> 1611 [penwidth=\"1.6931471805599454\", color=black];\n\t1589 -> 198 [penwidth=1, color=black];\n\t1589 -> 264 [penwidth=1, color=black];\n\t1589 -> 270 [penwidth=1, color=black];\n\t1589 -> 1528 [penwidth=1, color=black];\n\t1590 -> 1518 [penwidth=1, color=black];\n\t1591 -> 1518 [penwidth=1, color=black];\n\t1592 -> 1518 [penwidth=1, color=black];\n\t1593 -> 1518 [penwidth=1, color=black];\n\t1594 -> 356 [penwidth=1, color=black];\n\t1595 -> 362 [penwidth=1, color=black];\n\t1595 -> 363 [penwidth=1, color=black];\n\t1595 -> 364 [penwidth=1, color=black];\n\t1596 -> 333 [penwidth=1, color=black];\n\t1596 -> 1529 [penwidth=1, color=black];\n\t1597 -> 96 [penwidth=1, color=black];\n\t1597 -> 120 [penwidth=1, color=black];\n\t1597 -> 124 [penwidth=1, color=black];\n\t1597 -> 127 [penwidth=1, color=black];\n\t1597 -> 138 [penwidth=1, color=black];\n\t1597 -> 158 [penwidth=1, color=black];\n\t1597 -> 195 [penwidth=1, color=black];\n\t1597 -> 331 [penwidth=1, color=black];\n\t1597 -> 1529 [penwidth=1, color=black];\n\t1598 -> 1518 [penwidth=1, color=black];\n\t1599 -> 391 [penwidth=1, color=black];\n\t1600 -> 1518 [penwidth=1, color=black];\n\t1602 -> 1521 [penwidth=1, color=black];\n\t1604 -> 1657 [penwidth=1, color=black];\n\t1605 -> 1658 [penwidth=1, color=black];\n\t1607 -> 1356 [penwidth=1, color=black];\n\t1610 -> 152 [penwidth=1, color=black];\n\t1611 -> 407 [penwidth=1, color=black];\n\t1611 -> 1612 [penwidth=\"1.6931471805599454\", color=black];\n\t1612 -> 1601 [penwidth=1, color=black];\n\t1612 -> 1889 [penwidth=1, color=black];\n\t1614 -> 1657 [penwidth=1, color=black];\n\t1616 -> 1657 [penwidth=1, color=black];\n\t1617 -> 1613 [penwidth=1, color=black];\n\t1617 -> 1656 [penwidth=\"2.386294361119891\", color=black];\n\t1619 -> 1655 [penwidth=1, color=black];\n\t1619 -> 1776 [penwidth=\"1.6931471805599454\", color=black];\n\t1620 -> 1773 [penwidth=\"1.6931471805599454\", color=black];\n\t1620 -> 1774 [penwidth=\"1.6931471805599454\", color=black];\n\t1620 -> 1775 [penwidth=\"1.6931471805599454\", color=black];\n\t1620 -> 1778 [penwidth=\"1.6931471805599454\", color=black];\n\t1621 -> 1655 [penwidth=1, color=black];\n\t1621 -> 1777 [penwidth=\"1.6931471805599454\", color=black];\n\t1622 -> 82 [penwidth=\"1.6931471805599454\", color=black];\n\t1622 -> 1604 [penwidth=1, color=black];\n\t1623 -> 316 [penwidth=\"1.6931471805599454\", color=black];\n\t1623 -> 317 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 85 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 86 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 87 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 88 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 93 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 94 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 104 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 105 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 108 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 109 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 110 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 111 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 113 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 117 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 118 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 121 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 123 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 125 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 126 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 130 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 131 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 132 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 133 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 134 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 141 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 143 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 144 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 145 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 149 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 154 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 160 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 163 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 164 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 165 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 166 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 167 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 175 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 176 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 177 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 178 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 179 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 180 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 181 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 182 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 188 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 189 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 190 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 202 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 205 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 207 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 212 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 213 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 214 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 215 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 216 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 217 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 218 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 219 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 220 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 221 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 222 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 223 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 224 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 226 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 227 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 228 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 229 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 230 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 233 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 234 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 235 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 239 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 245 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 246 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 248 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 249 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 251 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 252 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 253 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 259 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 265 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 269 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 272 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 273 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 276 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 277 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 278 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 279 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 280 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 282 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 287 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 289 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 290 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 291 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 293 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 294 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 296 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 297 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 305 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 308 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 309 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 312 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 313 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 314 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 315 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 319 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 323 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 324 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 327 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 329 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 330 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 334 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 336 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 337 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 340 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 342 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 344 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 345 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 347 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 348 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 350 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 351 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 352 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 354 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 359 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 361 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 366 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 367 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 370 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 371 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 372 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 373 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 374 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 375 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 376 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 379 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 385 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 386 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 388 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 394 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 395 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 396 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 398 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 399 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 401 [penwidth=\"1.6931471805599454\", color=black];\n\t1624 -> 1604 [penwidth=\"2.386294361119891\", color=black];\n\t1624 -> 1660 [penwidth=\"4.526360524616162\", color=black];\n\t1624 -> 1664 [penwidth=1, color=black];\n\t1625 -> 644 [penwidth=\"1.6931471805599454\", color=black];\n\t1625 -> 1074 [penwidth=\"2.09861228866811\", color=black];\n\t1625 -> 1075 [penwidth=\"1.6931471805599454\", color=black];\n\t1626 -> 645 [penwidth=\"1.6931471805599454\", color=black];\n\t1627 -> 122 [penwidth=\"1.6931471805599454\", color=black];\n\t1627 -> 281 [penwidth=\"1.6931471805599454\", color=black];\n\t1628 -> 263 [penwidth=\"1.6931471805599454\", color=black];\n\t1628 -> 400 [penwidth=\"1.6931471805599454\", color=black];\n\t1628 -> 1660 [penwidth=1, color=black];\n\t1629 -> 1604 [penwidth=\"2.09861228866811\", color=black];\n\t1630 -> 1608 [penwidth=1, color=black];\n\t1630 -> 1660 [penwidth=1, color=black];\n\t1631 -> 1236 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1237 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1238 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1239 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1240 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1241 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1242 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1243 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1244 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1248 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1249 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1251 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1252 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1258 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1259 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1261 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1262 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1264 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1267 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1269 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1270 [penwidth=\"1.6931471805599454\", color=black];\n\t1631 -> 1271 [penwidth=\"1.6931471805599454\", color=black];\n\t1632 -> 1254 [penwidth=\"1.6931471805599454\", color=black];\n\t1632 -> 1255 [penwidth=\"1.6931471805599454\", color=black];\n\t1632 -> 1613 [penwidth=1, color=black];\n\t1633 -> 1266 [penwidth=\"1.6931471805599454\", color=black];\n\t1633 -> 1268 [penwidth=\"1.6931471805599454\", color=black];\n\t1633 -> 1656 [penwidth=1, color=black];\n\t1634 -> 1260 [penwidth=\"1.6931471805599454\", color=black];\n\t1634 -> 1656 [penwidth=1, color=black];\n\t1635 -> 1233 [penwidth=\"1.6931471805599454\", color=black];\n\t1635 -> 1656 [penwidth=1, color=black];\n\t1636 -> 1250 [penwidth=\"1.6931471805599454\", color=black];\n\t1636 -> 1257 [penwidth=\"1.6931471805599454\", color=black];\n\t1636 -> 1265 [penwidth=\"1.6931471805599454\", color=black];\n\t1636 -> 1613 [penwidth=1, color=black];\n\t1636 -> 1656 [penwidth=1, color=black];\n\t1636 -> 1660 [penwidth=1, color=black];\n\t1637 -> 187 [penwidth=\"1.6931471805599454\", color=black];\n\t1637 -> 321 [penwidth=\"1.6931471805599454\", color=black];\n\t1637 -> 365 [penwidth=\"1.6931471805599454\", color=black];\n\t1637 -> 1610 [penwidth=1, color=black];\n\t1637 -> 1657 [penwidth=1, color=black];\n\t1637 -> 1660 [penwidth=1, color=black];\n\t1638 -> 83 [penwidth=1, color=black];\n\t1638 -> 209 [penwidth=\"1.6931471805599454\", color=black];\n\t1638 -> 210 [penwidth=\"1.6931471805599454\", color=black];\n\t1638 -> 1603 [penwidth=1, color=black];\n\t1638 -> 1660 [penwidth=1, color=black];\n\t1639 -> 206 [penwidth=\"1.6931471805599454\", color=black];\n\t1639 -> 1604 [penwidth=1, color=black];\n\t1640 -> 208 [penwidth=\"2.386294361119891\", color=black];\n\t1640 -> 211 [penwidth=1, color=black];\n\t1641 -> 307 [penwidth=\"1.6931471805599454\", color=black];\n\t1642 -> 286 [penwidth=\"1.6931471805599454\", color=black];\n\t1643 -> 283 [penwidth=\"1.6931471805599454\", color=black];\n\t1644 -> 299 [penwidth=1, color=black];\n\t1644 -> 607 [penwidth=1, color=black];\n\t1644 -> 608 [penwidth=1, color=black];\n\t1644 -> 609 [penwidth=1, color=black];\n\t1644 -> 1659 [penwidth=1, color=black];\n\t1645 -> 1607 [penwidth=1, color=black];\n\t1645 -> 1660 [penwidth=1, color=black];\n\t1647 -> 300 [penwidth=\"1.6931471805599454\", color=black];\n\t1647 -> 358 [penwidth=\"1.6931471805599454\", color=black];\n\t1647 -> 1604 [penwidth=1, color=black];\n\t1647 -> 1662 [penwidth=1, color=black];\n\t1648 -> 89 [penwidth=\"1.6931471805599454\", color=black];\n\t1648 -> 1601 [penwidth=1, color=black];\n\t1649 -> 152 [penwidth=\"2.09861228866811\", color=black];\n\t1649 -> 161 [penwidth=\"1.6931471805599454\", color=black];\n\t1649 -> 225 [penwidth=1, color=black];\n\t1649 -> 304 [penwidth=\"2.09861228866811\", color=black];\n\t1649 -> 1657 [penwidth=1, color=black];\n\t1649 -> 1660 [penwidth=1, color=black];\n\t1650 -> 322 [penwidth=\"1.6931471805599454\", color=black];\n\t1651 -> 264 [penwidth=\"1.6931471805599454\", color=black];\n\t1651 -> 1660 [penwidth=1, color=black];\n\t1652 -> 356 [penwidth=\"2.386294361119891\", color=black];\n\t1652 -> 1659 [penwidth=\"1.6931471805599454\", color=black];\n\t1653 -> 362 [penwidth=\"1.6931471805599454\", color=black];\n\t1653 -> 363 [penwidth=1, color=black];\n\t1653 -> 364 [penwidth=\"1.6931471805599454\", color=black];\n\t1654 -> 391 [penwidth=\"1.6931471805599454\", color=black];\n\t1654 -> 1659 [penwidth=1, color=black];\n\t1655 -> 1900 [penwidth=1, color=black];\n\t1656 -> 1657 [penwidth=1, color=black];\n\t1657 -> 1658 [penwidth=1, color=black];\n\t1657 -> 1900 [penwidth=1, color=black];\n\t1659 -> 1900 [penwidth=1, color=black];\n\t1660 -> 1605 [penwidth=1, color=black];\n\t1660 -> 1663 [penwidth=1, color=black];\n\t1661 -> 1250 [penwidth=\"1.6931471805599454\", color=black];\n\t1661 -> 1257 [penwidth=\"1.6931471805599454\", color=black];\n\t1661 -> 1265 [penwidth=\"1.6931471805599454\", color=black];\n\t1662 -> 356 [penwidth=1, color=black];\n\t1663 -> 1606 [penwidth=1, color=black];\n\t1663 -> 1609 [penwidth=1, color=black];\n\t1665 -> 1885 [penwidth=1, color=black];\n\t1671 -> 1668 [penwidth=\"2.386294361119891\", color=black];\n\t1671 -> 1670 [penwidth=\"2.386294361119891\", color=black];\n\t1672 -> 1667 [penwidth=1, color=black];\n\t1672 -> 1668 [penwidth=1, color=black];\n\t1672 -> 1669 [penwidth=1, color=black];\n\t1672 -> 1670 [penwidth=1, color=black];\n\t1672 -> 1672 [penwidth=1, color=black];\n\t1673 -> 1672 [penwidth=1, color=black];\n\t1673 -> 1674 [penwidth=1, color=black];\n\t1673 -> 1678 [penwidth=1, color=black];\n\t1674 -> 1668 [penwidth=\"1.6931471805599454\", color=black];\n\t1674 -> 1670 [penwidth=1, color=black];\n\t1674 -> 1671 [penwidth=1, color=black];\n\t1674 -> 1674 [penwidth=1, color=black];\n\t1674 -> 1675 [penwidth=1, color=black];\n\t1674 -> 1676 [penwidth=1, color=black];\n\t1675 -> 1668 [penwidth=1, color=black];\n\t1675 -> 1670 [penwidth=1, color=black];\n\t1676 -> 1668 [penwidth=\"1.6931471805599454\", color=black];\n\t1676 -> 1670 [penwidth=\"1.6931471805599454\", color=black];\n\t1677 -> 1668 [penwidth=1, color=black];\n\t1677 -> 1670 [penwidth=1, color=black];\n\t1677 -> 1678 [penwidth=1, color=orange];\n\t1678 -> 1677 [penwidth=1, color=orange];\n\t1693 -> 1692 [penwidth=1, color=black];\n\t1694 -> 600 [penwidth=1, color=black];\n\t1694 -> 602 [penwidth=1, color=black];\n\t1694 -> 603 [penwidth=1, color=black];\n\t1694 -> 1682 [penwidth=1, color=black];\n\t1694 -> 1684 [penwidth=\"1.6931471805599454\", color=black];\n\t1694 -> 1687 [penwidth=1, color=black];\n\t1696 -> 1695 [penwidth=1, color=black];\n\t1698 -> 1697 [penwidth=1, color=black];\n\t1703 -> 1701 [penwidth=\"1.6931471805599454\", color=black];\n\t1703 -> 1702 [penwidth=\"1.6931471805599454\", color=black];\n\t1704 -> 1714 [penwidth=\"1.6931471805599454\", color=black];\n\t1705 -> 601 [penwidth=1, color=black];\n\t1705 -> 1683 [penwidth=1, color=black];\n\t1705 -> 1700 [penwidth=1, color=black];\n\t1705 -> 1701 [penwidth=1, color=black];\n\t1705 -> 1702 [penwidth=1, color=black];\n\t1706 -> 601 [penwidth=1, color=black];\n\t1706 -> 603 [penwidth=1, color=black];\n\t1706 -> 1682 [penwidth=1, color=black];\n\t1706 -> 1683 [penwidth=1, color=black];\n\t1706 -> 1684 [penwidth=1, color=black];\n\t1706 -> 1685 [penwidth=1, color=black];\n\t1706 -> 1687 [penwidth=1, color=black];\n\t1706 -> 1688 [penwidth=1, color=black];\n\t1707 -> 603 [penwidth=1, color=black];\n\t1707 -> 1688 [penwidth=1, color=black];\n\t1707 -> 1713 [penwidth=1, color=black];\n\t1707 -> 1714 [penwidth=1, color=black];\n\t1711 -> 178 [penwidth=1, color=black];\n\t1711 -> 372 [penwidth=1, color=black];\n\t1711 -> 1680 [penwidth=1, color=black];\n\t1711 -> 1690 [penwidth=\"1.6931471805599454\", color=black];\n\t1712 -> 1711 [penwidth=1, color=black];\n\t1718 -> 1760 [penwidth=1, color=black];\n\t1719 -> 1387 [penwidth=1, color=black];\n\t1719 -> 1439 [penwidth=1, color=black];\n\t1719 -> 1441 [penwidth=1, color=black];\n\t1720 -> 1719 [penwidth=1, color=black];\n\t1720 -> 1734 [penwidth=1, color=black];\n\t1721 -> 1393 [penwidth=1, color=black];\n\t1721 -> 1441 [penwidth=1, color=black];\n\t1721 -> 1442 [penwidth=1, color=black];\n\t1722 -> 1711 [penwidth=1, color=black];\n\t1722 -> 1724 [penwidth=\"1.6931471805599454\", color=black];\n\t1722 -> 1726 [penwidth=1, color=black];\n\t1723 -> 1712 [penwidth=1, color=black];\n\t1723 -> 1719 [penwidth=1, color=black];\n\t1723 -> 1725 [penwidth=\"1.6931471805599454\", color=black];\n\t1723 -> 1726 [penwidth=1, color=black];\n\t1724 -> 1359 [penwidth=1, color=black];\n\t1724 -> 1373 [penwidth=1, color=black];\n\t1724 -> 1387 [penwidth=1, color=black];\n\t1725 -> 1393 [penwidth=1, color=black];\n\t1725 -> 1442 [penwidth=1, color=black];\n\t1725 -> 1724 [penwidth=\"1.6931471805599454\", color=black];\n\t1725 -> 1734 [penwidth=1, color=black];\n\t1726 -> 1435 [penwidth=\"1.6931471805599454\", color=black];\n\t1726 -> 1442 [penwidth=1, color=black];\n\t1726 -> 1695 [penwidth=1, color=black];\n\t1726 -> 1762 [penwidth=1, color=black];\n\t1727 -> 1435 [penwidth=\"2.09861228866811\", color=black];\n\t1727 -> 1682 [penwidth=1, color=black];\n\t1727 -> 1684 [penwidth=1, color=black];\n\t1727 -> 1687 [penwidth=1, color=black];\n\t1728 -> 1371 [penwidth=1, color=black];\n\t1728 -> 1387 [penwidth=1, color=black];\n\t1728 -> 1391 [penwidth=\"2.09861228866811\", color=black];\n\t1728 -> 1433 [penwidth=1, color=black];\n\t1728 -> 1435 [penwidth=\"1.6931471805599454\", color=black];\n\t1728 -> 1697 [penwidth=1, color=black];\n\t1728 -> 1758 [penwidth=1, color=black];\n\t1728 -> 1764 [penwidth=1, color=black];\n\t1732 -> 1373 [penwidth=1, color=black];\n\t1732 -> 1387 [penwidth=1, color=black];\n\t1732 -> 1681 [penwidth=1, color=black];\n\t1732 -> 1726 [penwidth=1, color=black];\n\t1733 -> 1373 [penwidth=1, color=black];\n\t1733 -> 1387 [penwidth=1, color=black];\n\t1733 -> 1391 [penwidth=1, color=black];\n\t1733 -> 1432 [penwidth=1, color=black];\n\t1733 -> 1435 [penwidth=1, color=black];\n\t1733 -> 1689 [penwidth=\"1.6931471805599454\", color=black];\n\t1733 -> 1692 [penwidth=1, color=black];\n\t1733 -> 1760 [penwidth=1, color=black];\n\t1734 -> 1378 [penwidth=1, color=black];\n\t1734 -> 1441 [penwidth=1, color=black];\n\t1734 -> 1757 [penwidth=\"1.6931471805599454\", color=black];\n\t1735 -> 1721 [penwidth=1, color=black];\n\t1736 -> 1433 [penwidth=1, color=black];\n\t1736 -> 1440 [penwidth=1, color=black];\n\t1736 -> 1733 [penwidth=1, color=black];\n\t1736 -> 1755 [penwidth=1, color=black];\n\t1737 -> 1719 [penwidth=1, color=black];\n\t1737 -> 1722 [penwidth=1, color=black];\n\t1738 -> 1719 [penwidth=1, color=black];\n\t1738 -> 1732 [penwidth=1, color=black];\n\t1739 -> 1441 [penwidth=1, color=black];\n\t1739 -> 1694 [penwidth=1, color=black];\n\t1739 -> 1727 [penwidth=1, color=black];\n\t1740 -> 1760 [penwidth=1, color=black];\n\t1741 -> 1723 [penwidth=1, color=black];\n\t1741 -> 1734 [penwidth=1, color=black];\n\t1742 -> 1720 [penwidth=1, color=black];\n\t1742 -> 1732 [penwidth=1, color=black];\n\t1743 -> 1734 [penwidth=1, color=black];\n\t1744 -> 1470 [penwidth=1, color=black];\n\t1745 -> 1744 [penwidth=1, color=black];\n\t1747 -> 1470 [penwidth=\"1.6931471805599454\", color=black];\n\t1747 -> 1696 [penwidth=1, color=black];\n\t1747 -> 1699 [penwidth=1, color=black];\n\t1747 -> 1701 [penwidth=1, color=black];\n\t1747 -> 1702 [penwidth=1, color=black];\n\t1747 -> 1763 [penwidth=1, color=black];\n\t1747 -> 1871 [penwidth=1, color=black];\n\t1748 -> 1682 [penwidth=1, color=black];\n\t1748 -> 1684 [penwidth=1, color=black];\n\t1748 -> 1687 [penwidth=1, color=black];\n\t1749 -> 1470 [penwidth=1, color=black];\n\t1749 -> 1698 [penwidth=1, color=black];\n\t1749 -> 1759 [penwidth=1, color=black];\n\t1749 -> 1765 [penwidth=1, color=black];\n\t1749 -> 1871 [penwidth=\"1.6931471805599454\", color=black];\n\t1750 -> 1470 [penwidth=1, color=black];\n\t1750 -> 1714 [penwidth=1, color=black];\n\t1751 -> 1469 [penwidth=1, color=black];\n\t1751 -> 1470 [penwidth=\"1.6931471805599454\", color=black];\n\t1751 -> 1475 [penwidth=1, color=black];\n\t1751 -> 1689 [penwidth=1, color=black];\n\t1751 -> 1692 [penwidth=1, color=black];\n\t1751 -> 1871 [penwidth=1, color=black];\n\t1752 -> 1746 [penwidth=1, color=chartreuse];\n\t1753 -> 1752 [penwidth=1, color=black];\n\t1754 -> 1693 [penwidth=1, color=black];\n\t1754 -> 1751 [penwidth=1, color=black];\n\t1754 -> 1756 [penwidth=1, color=black];\n\t1754 -> 1871 [penwidth=1, color=black];\n\t1756 -> 1755 [penwidth=1, color=black];\n\t1757 -> 1373 [penwidth=1, color=black];\n\t1757 -> 1379 [penwidth=1, color=black];\n\t1757 -> 1380 [penwidth=1, color=black];\n\t1757 -> 1440 [penwidth=1, color=black];\n\t1757 -> 1441 [penwidth=1, color=black];\n\t1759 -> 1758 [penwidth=1, color=black];\n\t1760 -> 1679 [penwidth=1, color=black];\n\t1760 -> 1686 [penwidth=1, color=black];\n\t1760 -> 1689 [penwidth=1, color=black];\n\t1760 -> 1883 [penwidth=1, color=black];\n\t1760 -> 1884 [penwidth=1, color=black];\n\t1761 -> 1689 [penwidth=1, color=black];\n\t1763 -> 1762 [penwidth=1, color=black];\n\t1765 -> 1764 [penwidth=1, color=black];\n\t1766 -> 1700 [penwidth=1, color=black];\n\t1766 -> 1744 [penwidth=1, color=black];\n\t1766 -> 1747 [penwidth=1, color=black];\n\t1767 -> 1713 [penwidth=1, color=black];\n\t1767 -> 1744 [penwidth=1, color=black];\n\t1767 -> 1750 [penwidth=1, color=black];\n\t1768 -> 1691 [penwidth=1, color=black];\n\t1768 -> 1748 [penwidth=1, color=black];\n\t1769 -> 1679 [penwidth=1, color=black];\n\t1769 -> 1686 [penwidth=1, color=black];\n\t1769 -> 1689 [penwidth=1, color=black];\n\t1770 -> 1700 [penwidth=1, color=black];\n\t1770 -> 1745 [penwidth=1, color=black];\n\t1770 -> 1747 [penwidth=1, color=black];\n\t1771 -> 1713 [penwidth=1, color=black];\n\t1771 -> 1745 [penwidth=1, color=black];\n\t1771 -> 1750 [penwidth=1, color=black];\n\t1772 -> 1691 [penwidth=1, color=black];\n\t1772 -> 1745 [penwidth=1, color=black];\n\t1772 -> 1748 [penwidth=1, color=black];\n\t1779 -> 1785 [penwidth=1, color=black];\n\t1779 -> 1815 [penwidth=1, color=black];\n\t1779 -> 1846 [penwidth=1, color=black];\n\t1780 -> 1785 [penwidth=\"1.6931471805599454\", color=black];\n\t1781 -> 1773 [penwidth=\"1.6931471805599454\", color=black];\n\t1781 -> 1774 [penwidth=\"1.6931471805599454\", color=black];\n\t1781 -> 1775 [penwidth=\"1.6931471805599454\", color=black];\n\t1781 -> 1778 [penwidth=\"1.6931471805599454\", color=black];\n\t1782 -> 1789 [penwidth=\"1.6931471805599454\", color=black];\n\t1790 -> 1776 [penwidth=1, color=black];\n\t1790 -> 1783 [penwidth=1, color=black];\n\t1790 -> 1784 [penwidth=1, color=black];\n\t1790 -> 1785 [penwidth=1, color=black];\n\t1790 -> 1787 [penwidth=1, color=black];\n\t1790 -> 1791 [penwidth=1, color=black];\n\t1791 -> 1773 [penwidth=1, color=black];\n\t1791 -> 1774 [penwidth=1, color=black];\n\t1791 -> 1775 [penwidth=1, color=black];\n\t1791 -> 1778 [penwidth=1, color=black];\n\t1791 -> 1792 [penwidth=1, color=orange];\n\t1792 -> 1777 [penwidth=1, color=black];\n\t1792 -> 1786 [penwidth=1, color=black];\n\t1792 -> 1788 [penwidth=1, color=black];\n\t1792 -> 1789 [penwidth=1, color=black];\n\t1792 -> 1791 [penwidth=1, color=orange];\n\t1793 -> 1784 [penwidth=1, color=black];\n\t1794 -> 1783 [penwidth=1, color=black];\n\t1795 -> 1787 [penwidth=1, color=black];\n\t1796 -> 1785 [penwidth=1, color=black];\n\t1796 -> 1817 [penwidth=1, color=black];\n\t1796 -> 1848 [penwidth=1, color=black];\n\t1799 -> 1787 [penwidth=1, color=black];\n\t1800 -> 1785 [penwidth=1, color=black];\n\t1800 -> 1816 [penwidth=1, color=black];\n\t1800 -> 1849 [penwidth=1, color=black];\n\t1804 -> 1387 [penwidth=1, color=black];\n\t1807 -> 1728 [penwidth=1, color=black];\n\t1807 -> 1735 [penwidth=1, color=black];\n\t1807 -> 1776 [penwidth=1, color=black];\n\t1807 -> 1804 [penwidth=1, color=black];\n\t1808 -> 1773 [penwidth=1, color=black];\n\t1808 -> 1774 [penwidth=1, color=black];\n\t1808 -> 1775 [penwidth=1, color=black];\n\t1808 -> 1778 [penwidth=1, color=black];\n\t1809 -> 1721 [penwidth=1, color=black];\n\t1809 -> 1735 [penwidth=1, color=black];\n\t1809 -> 1736 [penwidth=1, color=black];\n\t1809 -> 1777 [penwidth=\"1.6931471805599454\", color=black];\n\t1809 -> 1804 [penwidth=\"1.6931471805599454\", color=black];\n\t1810 -> 1442 [penwidth=1, color=black];\n\t1810 -> 1723 [penwidth=1, color=black];\n\t1810 -> 1734 [penwidth=1, color=black];\n\t1810 -> 1773 [penwidth=1, color=black];\n\t1811 -> 1380 [penwidth=1, color=black];\n\t1811 -> 1441 [penwidth=1, color=black];\n\t1812 -> 1470 [penwidth=1, color=black];\n\t1813 -> 1754 [penwidth=1, color=black];\n\t1813 -> 1786 [penwidth=1, color=black];\n\t1813 -> 1788 [penwidth=1, color=black];\n\t1814 -> 1784 [penwidth=1, color=black];\n\t1815 -> 1818 [penwidth=1, color=orange];\n\t1816 -> 1819 [penwidth=1, color=orange];\n\t1817 -> 1820 [penwidth=1, color=orange];\n\t1818 -> 1773 [penwidth=1, color=black];\n\t1818 -> 1775 [penwidth=1, color=black];\n\t1818 -> 1778 [penwidth=1, color=black];\n\t1818 -> 1815 [penwidth=1, color=orange];\n\t1818 -> 1826 [penwidth=1, color=black];\n\t1818 -> 1832 [penwidth=1, color=black];\n\t1818 -> 1833 [penwidth=1, color=black];\n\t1818 -> 1861 [penwidth=1, color=black];\n\t1819 -> 1773 [penwidth=1, color=black];\n\t1819 -> 1774 [penwidth=1, color=black];\n\t1819 -> 1775 [penwidth=1, color=black];\n\t1819 -> 1778 [penwidth=1, color=black];\n\t1819 -> 1816 [penwidth=1, color=orange];\n\t1819 -> 1826 [penwidth=1, color=black];\n\t1819 -> 1834 [penwidth=1, color=black];\n\t1819 -> 1837 [penwidth=1, color=black];\n\t1819 -> 1838 [penwidth=1, color=black];\n\t1819 -> 1861 [penwidth=1, color=black];\n\t1820 -> 1775 [penwidth=1, color=black];\n\t1820 -> 1778 [penwidth=1, color=black];\n\t1820 -> 1817 [penwidth=1, color=orange];\n\t1820 -> 1826 [penwidth=1, color=black];\n\t1820 -> 1836 [penwidth=1, color=black];\n\t1820 -> 1839 [penwidth=1, color=black];\n\t1821 -> 1749 [penwidth=1, color=black];\n\t1821 -> 1752 [penwidth=1, color=black];\n\t1821 -> 1783 [penwidth=1, color=black];\n\t1821 -> 1784 [penwidth=1, color=black];\n\t1821 -> 1785 [penwidth=1, color=black];\n\t1821 -> 1787 [penwidth=1, color=black];\n\t1821 -> 1812 [penwidth=1, color=black];\n\t1822 -> 1773 [penwidth=1, color=black];\n\t1822 -> 1774 [penwidth=1, color=black];\n\t1822 -> 1775 [penwidth=1, color=black];\n\t1822 -> 1778 [penwidth=1, color=black];\n\t1823 -> 1752 [penwidth=1, color=black];\n\t1823 -> 1789 [penwidth=1, color=black];\n\t1823 -> 1812 [penwidth=1, color=black];\n\t1823 -> 1813 [penwidth=1, color=black];\n\t1825 -> 1753 [penwidth=1, color=black];\n\t1825 -> 1789 [penwidth=1, color=black];\n\t1825 -> 1812 [penwidth=1, color=black];\n\t1825 -> 1813 [penwidth=1, color=black];\n\t1826 -> 1786 [penwidth=1, color=black];\n\t1826 -> 1788 [penwidth=1, color=black];\n\t1826 -> 1789 [penwidth=1, color=black];\n\t1826 -> 1871 [penwidth=1, color=black];\n\t1827 -> 517 [penwidth=1, color=black];\n\t1827 -> 1845 [penwidth=1, color=black];\n\t1831 -> 1854 [penwidth=1, color=black];\n\t1831 -> 1860 [penwidth=1, color=black];\n\t1831 -> 1862 [penwidth=1, color=black];\n\t1832 -> 1680 [penwidth=1, color=black];\n\t1832 -> 1700 [penwidth=\"1.6931471805599454\", color=black];\n\t1832 -> 1847 [penwidth=1, color=black];\n\t1832 -> 1860 [penwidth=1, color=black];\n\t1832 -> 1863 [penwidth=1, color=black];\n\t1832 -> 1867 [penwidth=1, color=black];\n\t1832 -> 1868 [penwidth=1, color=black];\n\t1833 -> 1682 [penwidth=1, color=black];\n\t1833 -> 1835 [penwidth=1, color=black];\n\t1834 -> 1680 [penwidth=1, color=black];\n\t1834 -> 1847 [penwidth=1, color=black];\n\t1834 -> 1850 [penwidth=1, color=black];\n\t1834 -> 1856 [penwidth=1, color=black];\n\t1835 -> 1858 [penwidth=1, color=black];\n\t1835 -> 1868 [penwidth=1, color=black];\n\t1835 -> 1869 [penwidth=1, color=black];\n\t1836 -> 1684 [penwidth=1, color=black];\n\t1836 -> 1835 [penwidth=1, color=black];\n\t1837 -> 1681 [penwidth=1, color=black];\n\t1837 -> 1847 [penwidth=1, color=black];\n\t1837 -> 1850 [penwidth=1, color=black];\n\t1837 -> 1856 [penwidth=1, color=black];\n\t1838 -> 1687 [penwidth=1, color=black];\n\t1838 -> 1835 [penwidth=1, color=black];\n\t1839 -> 1831 [penwidth=1, color=black];\n\t1839 -> 1847 [penwidth=1, color=black];\n\t1839 -> 1850 [penwidth=1, color=black];\n\t1839 -> 1861 [penwidth=1, color=black];\n\t1842 -> 1845 [penwidth=1, color=black];\n\t1842 -> 1888 [penwidth=1, color=black];\n\t1846 -> 1830 [penwidth=1, color=black];\n\t1846 -> 1843 [penwidth=1, color=black];\n\t1846 -> 1865 [penwidth=1, color=black];\n\t1846 -> 1870 [penwidth=1, color=black];\n\t1847 -> 1851 [penwidth=1, color=black];\n\t1848 -> 1684 [penwidth=1, color=black];\n\t1848 -> 1830 [penwidth=1, color=black];\n\t1848 -> 1851 [penwidth=1, color=black];\n\t1848 -> 1865 [penwidth=1, color=black];\n\t1848 -> 1867 [penwidth=1, color=black];\n\t1848 -> 1870 [penwidth=1, color=black];\n\t1849 -> 1830 [penwidth=1, color=black];\n\t1849 -> 1841 [penwidth=1, color=black];\n\t1849 -> 1844 [penwidth=1, color=black];\n\t1849 -> 1853 [penwidth=1, color=black];\n\t1849 -> 1867 [penwidth=1, color=black];\n\t1849 -> 1870 [penwidth=1, color=black];\n\t1850 -> 1852 [penwidth=1, color=black];\n\t1854 -> 1840 [penwidth=1, color=chartreuse];\n\t1855 -> 1828 [penwidth=\"2.09861228866811\", color=black];\n\t1855 -> 1857 [penwidth=1, color=black];\n\t1856 -> 1828 [penwidth=1, color=black];\n\t1856 -> 1855 [penwidth=1, color=black];\n\t1856 -> 1860 [penwidth=1, color=black];\n\t1856 -> 1866 [penwidth=1, color=black];\n\t1857 -> 1888 [penwidth=1, color=black];\n\t1858 -> 1830 [penwidth=1, color=black];\n\t1858 -> 1851 [penwidth=\"1.6931471805599454\", color=black];\n\t1859 -> 1830 [penwidth=1, color=black];\n\t1859 -> 1852 [penwidth=\"1.6931471805599454\", color=black];\n\t1860 -> 1830 [penwidth=1, color=black];\n\t1860 -> 1870 [penwidth=\"1.6931471805599454\", color=black];\n\t1861 -> 1847 [penwidth=1, color=black];\n\t1861 -> 1850 [penwidth=1, color=black];\n\t1861 -> 1858 [penwidth=1, color=black];\n\t1861 -> 1859 [penwidth=\"1.6931471805599454\", color=black];\n\t1864 -> 1681 [penwidth=1, color=black];\n\t1866 -> 1829 [penwidth=1, color=black];\n\t1867 -> 1845 [penwidth=1, color=black];\n\t1868 -> 1829 [penwidth=1, color=black];\n\t1872 -> 1872 [penwidth=\"1.6931471805599454\", color=black];\n\t1873 -> 1873 [penwidth=\"1.6931471805599454\", color=black];\n\t1876 -> 1874 [penwidth=1, color=black];\n\t1876 -> 1882 [penwidth=1, color=black];\n\t1877 -> 1883 [penwidth=1, color=black];\n\t1878 -> 1881 [penwidth=1, color=chartreuse];\n\t1879 -> 1877 [penwidth=1, color=chartreuse];\n\t1882 -> 1874 [penwidth=1, color=black];\n\t1885 -> 1886 [penwidth=1, color=black];\n\t1886 -> 1875 [penwidth=1, color=chartreuse];\n\t1887 -> 144 [penwidth=1, color=black];\n\t1887 -> 219 [penwidth=\"1.6931471805599454\", color=black];\n\t1887 -> 348 [penwidth=1, color=black];\n\t1887 -> 367 [penwidth=1, color=black];\n}\n" graphviz-2999.20.2.0/TODO.md0000644000000000000000000000323614536315671013334 0ustar0000000000000000 Future Plans for graphviz ========================= This is a list of planned feature improvements to graphviz along with an indication of when it's likely to be implemented (note that these time scales are in relation to releases, not actual time; however, it is quite possible that the order will not be adhered to). Short term ---------- * Quickstart-style documentation to help users get going with graphviz quickly. * Add nicer syntax for record labels, and specifying ports in Monadic Dot graphs. * Add support for custom shapes; in particular, a nice way of re-defining the `Shape` datatype (as just adding a non-nullary constructor would make it unwieldy to make sure tests, etc. were kept up-to-date). * Define new classes to distinguish between printing/parsing Attribute values and other values (as only the former requires quoted variants). * Clean up AttributeGenerator and get it to use a better pretty-printing library. Medium term ----------- * Improve the test suite such that the generated `DotGraph` values are valid (and thus can be passed to Graphviz proper). This may not in fact be possible as guaranteeing an arbitrary `Attribute` is valid is rather tricky (as the value itself needs to be verified, especially stateful ones). * Switch to a proper test-suite library rather than the hand-rolled one currently being used. * Add support for clusters as endpoints of edges. Long term --------- * Allow usage of non-FGL graphs with graphviz. This will require implementing a separate library to represent graphs (see initial discussions about this [here](http://www.haskell.org/pipermail/haskell-cafe/2009-June/063402.html)). graphviz-2999.20.2.0/Changelog.md0000644000000000000000000010116514536315671014456 0ustar0000000000000000 Release History and Changelog ============================= The following is information about what major changes have gone into each release. Changes in 2999.20.2.0 ---------------------- * Add `PrintDot` instances for `Word32` and `Word64`. * Dependency bumps. Changes in 2999.20.1.0 ---------------------- * Add `MonadFix` instance for `DotM` (thanks to **George Wilson**) * Fix exception catching for missing executables (thanks to **Kostas Dermentzis**) * Dependency bumps. Changes in 2999.20.0.4 ---------------------- * Dependency bumps. Changes in 2999.20.0.3 ---------------------- * Dependency bumps. Changes in 2999.20.0.2 ---------------------- * Fix Haddock issue (thanks to **Moritz Kiefer**) * Bump HSpec upper bound (thanks to **Moritz Kiefer**) * Make Hackage happier with Cabal-Version field Changes in 2999.20.0.1 ---------------------- * Allow building with temporary-1.3.*. Changes in 2999.20.0.0 ---------------------- * Can now create subgraphs using the Monadic representation. * Allow unescaped `-` and `'` in HTML labels (thanks to **Andrey Kartashov**) * Support for strict `Text` instances for printing/parsing. * Creating a Graph representation with `mkGraph` was not adding edges correctly (reported by **Joshua Chia**). * Test suite now uses HSpec, making it a lot easier to add tests for specific issues. * Builds with GHC 8.4.* (thanks to **Tony Day**). * Monoid and Semigroup instances for Monadic representation (thanks to **Chris Martin**). * Be more lenient in parsing some attributes (e.g. allow `top` instead of just `t` for `VerticalPlacement`). * Add new HTML attributes: `Columns`, `GradientAngle`, `Rows`, `Sides` and `Style`. * Improve/update the TestParsing executable to work on being able to parse all the sample `Dot` graphs shipped with Graphviz. * Bump dependencies. Changes in 2999.19.0.0 ---------------------- * Roll back change in 2999.18.1.0 for Monadic graphs, as they turn out to not actually work in practice (reported by **Lennart Spitzner**). * Add a `quickParams` value to help with testing graphs in ghci (requested by **Ian Jeffries**). * Fix parsing of edge chains (reported by **Jonas Collberg**). * Fix how seemingly numeric text literals are quoted (reported by **Joey Hess**). Changes in 2999.18.1.2 ---------------------- * Allow dlist-0.8, thanks to **Sean Leather**. * Properly allow QuickCheck-2.9. Changes in 2999.18.1.1 ---------------------- * Bump allowed version of QuickCheck for the test suite. Changes in 2999.18.1.0 ---------------------- * Monadic graphs can now have edges to and from lists of nodes, as requested by **Harold Carr**. * Compatible with GHC-8.* pre-releases. - Please note that there is currently a warning emitted on compilation by GHC-8.*; this has been reported [here](https://ghc.haskell.org/trac/ghc/ticket/11822). Changes in 2999.18.0.2 ---------------------- * Match new behaviour of `dot`, etc. in supporting edge specifications like `a, b -> c, d` (spotted by **Dilawar Singh**). Changes in 2999.18.0.1 ---------------------- * Loosened bound on `fgl-arbitrary`. Changes in 2999.18.0.0 ---------------------- * Now builds on GHC 7.10.*. * Attribute changes: - Added the `NoTranslate` attribute. - Add support for overlines in HTML labels. Both of these are available as of Graphviz 2.38.0, but were somehow overlooked in previous releases of this library. * Uses new `fgl-arbitrary` library for testing rather than custom instances for FGL graphs. * Migrated to git; central repository now on [GitHub](https://github.com/ivan-m/graphviz). Changes in 2999.17.0.2 ---------------------- * Augmentation tests are no longer run by default. This avoids problems where Graphviz is not installed/configured properly. * Use `.gv` for temporary files instead of `.dot`. Changes in 2999.17.0.1 ---------------------- * Allow usage of `transformers-0.4.*`, by **Sergei Trofimovich**. Changes in 2999.17.0.0 ---------------------- * Add support for Graphviz 2.32.0, 2.32.1, 2.34.0, 2.36.0 and 2.38.0: - **WARNING**: at least as of Graphviz-2.32.0, `dot -Tcanon` no longer produces Dot code that is in the format expected by the Canonical Dot representation in this library. As such, unless you're very sure of your sources you should _always_ use the Generalised representation for parsing (see also the new `FromGeneralisedDot` class mentioned below). - New attributes: + `XDotVersion` (as of 2.34.0) + `InputScale` (as of 2.36.0) + `OverlapShrink` (as of 2.36.0) - Changed attributes: + `Aspect` no longer available (as of 2.36.0) + New `ModeType` values for use with `sfdp`: `SpringMode` and `MaxEnt`. + `Weight` now takes a value of type `Number`, that explicitly distinguishes between `Doubles` and `Ints`. + `FixedSize` and `Normalize` now have their own types. + New `Shape`s: `Star` and `Underline` (as well as `Square` which seems to have been omitted from previous versions). - Other relevant changes: + `XDot` now takes an optional version. Note that this doesn't have any effect on how _graphviz_ works. + The default extension for Dot-graphs is now `.gv` rather than `.dot` to reflect Graphviz's changed conventions. * Other changes to the API: - Add the `FromGeneralisedDot` class, which provides a semi-inverse to `fromCanonical` in `DotRepr`. - `GraphID` now uses `Number` rather than separate `Int` and `Double` constructors; this only matters if you manually constructed or de-constructed `GraphID` values (`ToGraphID` still works). - Add the ability to parse a Dot graph "liberally": that is, if an `Attribute` doesn't match the specification, then let it fall back to an `UnknownAttribute`. This is still experimental, and requires more manual usage than the in-built commands (e.g. it isn't supported in the default round-tripping). - Now using the definition of `bracket` from `polyparse >= 1.9`. - Monadic representation now has `Functor` and `Applicative` instances to satisfy the up-coming changes in GHC 7.10. * Compilation time has been reduced in two ways: - The `Data.GraphViz.Attributes.Complete` module has been split up (but still exports the same API, so no need to import more modules). Whilst I haven't measured it, this should also reduce memory requirements for compilation. - The testsuite now uses the library explicitly, and thus no longer needs to re-compile half the library. * Bug-fixes: - Double values are now longer parseable without double quotes if they have an exponential term (to better match the definition). - It is no longer assumed when round-tripping that `dot -Tdot` generates canonicalised Dot graphs. * The `TestParsing` script is now directly buildable by Cabal using the `test-parsing` flag (the resulting executable is called `graphviz-testparsing`). This is not made an actual test-suite as not all files found will be actual Dot graphs, and it's known that it fails on some. Instead it's meant to be used as an indication of how well this library parses "real-world" Dot code. Changes in 2999.16.0.0 ---------------------- * Add support for Graphviz-2.30.0: - New attributes: + `Area` + `Head_LP` + `LayerListSep` + `LayerSelect` + `Tail_LP` + `XLP` - `BgColor`, `Color` and `FillColor` now take a list of colors with optional weightings. - Layer handling now supports layer sub-ranges. - Added the voronoi-based option to `Overlap`. - Added the `Striped` and `Wedged` styles. * Updates to attributes and their values: - The following attributes have had their values changed to better reflect what they represent: + `FontPath` takes a `Path` value. + `Layout` takes a `GraphvizCommand` (and thus `GraphvizCommand` has been moved to `Data.GraphViz.Attributes.Complete`). - Added `MDS` to `Model` (which had somehow been overlooked). - Various attributes now have defaults added/updated/removed if wrong. - Removed the following deprecated attributes: + `ShapeFile` + `Z` * Now any value that has a defined default can be parsed when the Dot code just has `attribute=""` (which `dot -Tcanon` is fond of doing to "reset" attributes). * `GraphvizCommand` now defines `Sfdp` (which had somehow been overlooked up till now). * The `canonicalise` and related functions have been re-written; whilst there might be some cases where their behaviour does not fully match how `dot -Tcanon` and `tred` behave (due to the interaction of various attributes), the new implementation is much more sane. * Use temporary files rather than pipes when running dot, etc. Makes it more portable, and also avoids issues where dot, etc. use 100% CPU when a graph is passed in via stdin. Original patch by **Henning Thielemann**. * `renderCompactDot` now outputs to just one line (which means it's shorter, but more difficult to read for a human). * The QuickCheck instances are a bit smarter now to avoid having such ugly huge outputs when a test fails. * More documentation to help you understand what certain data types are for, etc. Changes in 2999.15.0.1 ---------------------- * Fixed bug where `canonicalise` and related functions did not properly deal with attributes of a single node or edge within a sub-graph. Changes in 2999.15.0.0 ---------------------- * The repository is now hosted on [hub.darcs.net](http://hub.darcs.net/ivanm/graphviz), and using the bug-tracker there. * Updates to various `Attribute` definitions: - The list of available shapes has been expanded to take into account the new synthetic biology shapes. - The `Size` and `FontNames` attributes now have specified data types. - The optional start and end points for `Spline`s were previously the wrong way round; this has now been fixed. - Explicitly only print 2-dimensional `Point` values for `Rect` and `DPoint` (previously only 2-dimensional values where parsed, but it was possible to print a 3-dimensional value). - HTML-like labels previously disallowed empty textual label components when parsing; spotted by **Daniel Hummel**. * `GraphvizParams` now lets you specify whether a "cluster" is actually a cluster or a sub-graph. Requested by **Gabor Greif**. * Fixed an error where printing edges whose attributes contained a `ColorScheme` attribute, that attribute would stay in the state and the old color scheme would override the _parent's_ state. * Previously, some malformed attributes were accepted when being parsed as they silently became parsed as an `UnknownAttribute`. Now, attributes where the attribute name and the equal sign are successfully parsed **but** the value of the attribute is _not_ successfully parse will throw an unrecoverable error. **Note**: this does mean that some Dot graphs that are accepted by Graphviz (as they separate tokenizing from parsing; as such something like `"0.1"` is successfully accepted as an integer, specifically `0`) are no longer accepted when parsing them in. * Miscellaneous parsing improvements: - Whilst not specified anywhere, Graphviz seems to treat empty quotes as values for attributes expecting a number as their default; as such, this is now taken into account when parsing. - `DPoint` values can now parse an optional `+` prefix. - Whitespaces after commas in HSV colors are now accepted. * Error messages from parsing are improved to help you track down where the parsing error occurred (in that it's easier to find which attribute failed to parse, etc.). * Some parsing combinators are no longer publicly accessible, but shouldn't be needed by end users anyway (as they were there for parsing the Attribute data type). Changes in 2999.14.1.0 ---------------------- * Add `isGraphvizInstalled` and `quitWithoutGraphviz` for programs to test whether Graphviz has been installed (as previous attempts at doing so via actual calls to dot, neato, etc. weren't working and would be too verbose anyway). Changes in 2999.14.0.0 ---------------------- * Added an instance of `Labellable` for strict `Text` values, as requested by **Erik Rantapaa**. Changes in 2999.13.0.3 ---------------------- * Allow usage of transformers-0.3.*. Spotted by **Peter Simons**. Changes in 2999.13.0.2 ---------------------- * The `String` instance for `ToGraphID` requires the `TypeSynonymInstances` pragma (at least on GHC < 7.4). Spotted by **Gregory Guthrie**. Changes in 2999.13.0.1 ---------------------- * Fixed Haddock typos. Changes in 2999.13.0.0 ---------------------- * Added support for the `osage` and `patchwork` visualisation tools, available as of Graphviz-2.28.0. * Updated attributes as of Graphviz-2.28.0: - `SVG` colors are now supported, and the support for different colors has been revamped. - `overlap=false` is now equivalent to `overlap=prism` and the `RemoveOverlaps` option has been removed. - `LabelScheme` and `Rotation` are new attributes for use with `sfdp`. - `Scale` is a new attribute for use with `twopi`. - Add new italics, bold, underline, superscript and subscript options for HTML-like labels. - `LHeight` and `LWidth` for getting the height and width of the root graph and clusters. * Updated attributes from the current development branch of Graphviz (i.e. 2.29.*). Please note that these will probably not work yet, but are implemented now for future-proofing. - A new style for edges: `Tapered`. - `XLabel` allows you to specify labels external to a node or edge. `ForceLabels` allow you to specify that these should be drawn even when they will cause overlaps. - `ImagePath` allows you to specify where to search for images. - HTML-like labels now support `ID` values as well as horizontal and vertical rules. - `BgColor` and `FillColor` now take a list of colors: this allows gradient fills for graphs, clusters and nodes. The `Radial` style and `GradientAngle` are also used for this purpose. - `FillColor` is now used by edges to set the color of any arrows. - [WebP](http://en.wikipedia.org/wiki/WebP) output support added. * Other attribute changes: - Use a specified data type for the `Ordering` attribute rather than an arbitrary `Text` value, and provide a documented wrapper in `Data.GraphViz.Attributes`. - `Bb` has been renamed `BoundingBox`. - `ID` now only takes `EscString` (a type alias for `Text`) values rather than arbitrary `Label`s. - The `Data.GraphViz.Attributes.HTML` module has had all values re-named and is now meant to be imported qualified. It is also no longer re-exported from `Data.GraphViz.Attributes.Complete`. * The `ToGraphID` class provides a common wrapper to help create cluster identifiers, etc. * Cabal's `Test-Suite` functionality is now used. As part of this, the `Data.GraphViz.Testing` module and sub-modules are no longer exported by the library. * The new `Benchmark` support in Cabal-1.14 is now used for the benchmark script. * Dropped support for base-3. * The `Data.GraphViz.State` module is no longer exposed, as there's no need for users to use it. * Bugfixes: - Some corner cases in canonicalisation prevented it from being idempotent. - The `TestParsing` script will no longer crash and refuse to continue if an IO-based error (e.g. unable to successfully call `dot`) occurs. - A typo was spotted by **Gabor Greif**. Changes in 2999.12.0.4 ---------------------- * Parsing error messages have been cleared up, especially when parsing Dot graphs. This came about from trying to help **Uri J. Braun** with an error in his code (which took a while to diagnose as a problem with the node type). * Made more clear to people looking in `Data.GraphViz` who want to create Dot graphs by hand to look in `Data.GraphViz.Types` (came about when **Rustom Mody** stated he got confused trying to work out how to do this). * Fixed up augmentation; bug and fix spotted by **Max Rabkin**. * Fix up the TestParsing script to actually use the new type setup. It can also now take a single directory as an argument, and will try to parse all (non-recursive) files in that directory. Changes in 2999.12.0.3 ---------------------- * Fixes various mistakes in the Haddock documentation that slipped through (either in the `String -> Text` conversion or adding new modules and not checking their documentation thoroughly enough). Changes in 2999.12.0.2 ---------------------- * Forgot to explicitly list the module for Arbitrary instance for the graph representation. Changes in 2999.12.0.1 ---------------------- * Fix a bug that prevented graphviz from being built with GHC 7.2. Changes in 2999.12.0.0 ---------------------- Many large-level changes were done in this release; in rough categories these are: ### Conversions from other types * Can now more easily create Dot graphs from other graph-like data structures with the new `graphElemsToDot` function, which takes a list of nodes and edges. * It is now no longer possible to use `graphToDot`, etc. to create Dot graphs with anonymous clusters; all clusters must now have explicit names (note that uniqueness is not enforced, and it is still possible to directly create Dot graphs with anonymous clusters). ### Dot graph representations * The canonical graph representation has been moved to its own module: `Data.GraphViz.Types.Canonical`. * The generalised representation has had all its "G" and "g" prefixes removed. * Two new representations: - `Data.GraphViz.Types.Graph` allows graph-like manipulation of Dot code. - `Data.GraphViz.Types.Monadic` provides a monadic interface into building relatively static graphs, based upon the [_dotgen_](http://hackage.haskell.org/package/dotgen) library by Andy Gill. * The `DotRepr` class has been expanded, and three pseudo-classes have been provided to reduce type-class contexts in type signatures. ### Using and manipulation Dot graphs * Pure Haskell implementations of `dot -Tcanon` and `tred` are available in `Data.GraphViz.Algorithms`. * A new module is available for more direct low-level I/O with Dot graphs, including the ability to run custom commands as opposed to being limited to the standard dot, neato, etc. ### Attributes * `Data.GraphViz.Attributes` now contains a slimmed-down recommended list of attributes; the complete list can still be found in `Data.GraphViz.Attributes.Complete`. * The `charset` attribute is no longer available. * Functions for specifying custom attributes (for pre-processors, etc.) are available. ### Implementation * Now uses [`Text`](http://hackage.haskell.org/package/text) values rather than `String`s. Whilst performing this migration, the improvements in speed for both printing and parsing improved dramatically. - As part of this, human-readable Dot code is now produced by default. As such, the `prettyPrint` and `prettyPrint'` functions have been removed. * Now uses state-based printing and parsing, so that things like graph directedness, layer separators and color schemes can be taken into account. * Parsing large data-types (e.g. `Attributes`) now uses less back-tracking. * Now has a benchmarking script for testing printing and parsing speed. * Uses a custom exception type rather than a mish-mash of error, `Maybe`, `Either`, exception types from used libraries, etc. * Usage of UTF-8 is now enforced when doing I/O. If another encoding is required, the `Text` value that's printed/parsed has to be written/read from disk/network/etc. manually. ### Bug-Fixes * The `Rects` `Attribute` should be able to take a list of `Rect` values; error spotted by **Henning Gunther**. * In some cases, global attribute names were being printed without even an empty list (which doesn't match what dot, etc. expect). Changes in 2999.11.0.0 ---------------------- * Addition of the `Labellable` class (and its method `toLabel`) to make it easier to construct labels. * Backslashes (i.e. the `\` character) are now escaped/unescaped properly (bug spotted by **Han Joosten**). As part of this: - Dot-specific escapes such as `\N` are now also handled correctly, so the slash does not need to be escaped. - Newline (`'\n'`) characters in labels, etc. are escaped to centred-newlines in Dot code, but not unescaped. * `Point` values can now have the optional third dimension and end in a `!` to indicate that that position should be used (as input to Graphviz). * `LayerList` uses `LayerID` values, and now has a proper `shrink` implementation in the test suite. Changes in 2999.10.0.1 ---------------------- * Fixed a mistake in one of the source files that was made just to make [haskell-src-exts](http://hackage.haskell.org/package/haskell-src-exts) happier. * Fix the `Arbitrary` instance for `Point` in the testsuite (since there's only one constructor now). Changes in 2999.10.0.0 ---------------------- * Conversion of `FGL`-style graphs to `DotRepr` values is now achieved using the new `GraphvizParams` configuration type. This allows us to define a single parameter that stores all the conversion functions to pass around rather than having to pass around several functions. This also allows all the non-clustered and clustered functions to be collapsed together, whereas what used to be handled by the primed functions is now achieved by using the `setDirectedness` function. There are three default `GraphvizParams` available: - `defaultParams` provides some sensible defaults (no attributes or clustering). - `nonClusteredParams` is an alias of `defaultParams` where the clustering type is explicitly set to be `()` for cases where you don't want any clustering at all (whereas `defaultParams` allows you to set your own clustering functions). - `blankParams` sets all fields to be `undefined`; this is useful for situations where you have functions that will set some values for you and there is no sensible default you can use (mainly for the clustering function). * Expansion of the `DotRepr` class: - More common functions are now defined as methods (`getID`, etc.). - The ability to get more information about the structure of the `DotRepr` graph, as well as where all the `DotNode`s are, etc. - `graphNodes` now returns `DotNode`s defined only as part of `DotEdge`s, and will also merge duplicate `DotNode`s together. - `graphNodes` and `graphEdges` also return `GlobalAttributes` that apply to them. * The `Point` type now only has one constructor: `Point Double Double`. The `Int`-only constructor was present due to historical purposes and I thought that the `Pos` value for a `DotNode` would always be a pair of `Int`s; this turns out not to be the case. * `SortV` and `PrismOverlap` now only take `Word16` values rather than `Int`s, as they're not meant to allow negative values (the choice of using `Word16` rather than `Word` was arbitrary, and because it's unlikely those values will be large enough to require the larger values available in `Word`). * `NodeCluster` has been generalised to not have to take an `LNode` for the node type; the type alias `LNodeCluster` is available if you still want this. * Several documentation typos fixed, including one spotted by **Kevin Quick**. * The test-suite now allows running individual tests. Changes in 2999.9.0.0 --------------------- * graphviz now has an FAQ and an improved README as well as its own [homepage](http://projects.haskell.org/graphviz/). * Canonicalisation of `DotRepr` values is now available with the `canonicalise` function. * Add support for record labels; values are automatically escaped/unescaped. The `Record` and `MRecord` shapes have been added for use with these labels. **Requested by Minh Thu and Eric Kow.** * Add support for HTML-like values (this replaces the wrong and completely broken URL datatype). Strings are automatically escaped/unescaped. * Named `PortPos` values are now accepted (as required for record and HTML-like labels). * `GraphID` no longer allows HTML-like values (since Graphviz doesn't seem to allow it). * `RankSep` takes a list of `Double` values as required. * `Attribute` has a new constructor `UnknownAttribute` for use when parsing deprecated Graphviz attributes in old Dot code. * Various parsing fixes; of special note: - Statements no longer need to end in a semi-colon; - Anonymous sub-graphs are now supported. - Edge statements can now handle node groupings (e.g. ` a -> {b c}`) as well as `portPos` values (e.g. `a:from -> b:to`). - Unquoted `String`s containing non-ASCII characters are now parsed properly (though they are assumed to be encoded with UTF-8). **Thanks to Jules Bean (aka quicksilver) for working out how to do this.** More specifically: almost all Dot files that ship with Graphviz, as documentation in the Linux kernel, etc. are now parseable. * A new script to assist in testing whether "real-world" Dot graphs are parseable. * Slight performance increase when parsing: whereas parsing is done case-insensitively, the "correct" case is now checked by default which has a moderate affect on parsing times. * Split lines are now able to be handled when parsing. Changes in 2999.8.0.0 --------------------- * Added support for generalised `DotGraph`s; this optional representation removes the restriction of ordering of Dot statements. This allows for greater flexibility of how to specify Dot code. As an offshoot from this, most relevant functions now utilise a new `DotRepr` class that work with both `DotGraph`s and the new `GDotGraph`s; this shouldn't affect any code already in use. * With the **prompting of Noam Lewis**, the augmentation functions have been revamped in two ways: - Now contains support for multiple edges. - The ability to perform "manual" augmentation if greater control is desired. * Add a preview function to quickly render and visualise an `FGL` graph using the `Xlib` canvas. * Added a pseudo-inverse of the `FGL -> Dot` functions (a graph is created, but the original node and edge labels are unrecoverable). * The `Printing` and `Parsing` modules have been moved (from `Data.GraphViz.Types` to `Data.GraphViz`). * Reworked file-generating commands such that they return the filename of the created file if successful. Changes in 2999.7.0.0 --------------------- * Updated and extended functions to interact with the Graphviz tools. This now includes: - a better listing of available output types; - distinguishing file outputs from canvas outputs; - ability to automatically add the correct file extension to file outputs - Return any errors if calling Graphviz failed rather than just printing them to stderr * Improved `Color` support: - fixed `ColorScheme` values - explicitly named `X11` colors - conversion to/from values from the [colour] library [colour]: http://www.haskell.org/haskellwiki/Colour * Removed `OrientationGraph`; problems with distinguishing it when parsing from node-based `Orientation` values; its functionality is duplicated by `Rotate`. * By default, the generated Dot code is now no longer indented; you can now use the `prettyPrint` functions in `Data.GraphViz` to produce readable Dot code. * Added a testsuite; this is buildable by building with `--flags-test`. Numerous printing and parsing bugs were picked up with this. Changes in 2999.6.0.0 --------------------- * Remove some `Shape` aliases and change capitalisation of others. * Properly parse and print IDs of clusters. * Allow `NodeCluster` values to have node types different from the `LNode` they come from. Changes in 2999.5.1.1 --------------------- * When used as labels, etc., the Dot keywords `node`, `edge`, `graph`, `digraph`, `subgraph`, and `strict` need to be quoted. **Spotted by Kathleen Fisher.** Changes in 2999.5.1.0 --------------------- * Potentially fixed the `graphvizWithHandle` bug; correct approach **spotted by Nikolas Mayr**. * Fixed up `Parsing` of various `Attribute` sub-values, especially `Point` and `Spline` (and hence `Pos`, which uses them). * Pre-process out comments and join together multi-line strings before parsing. * Properly parse `Doubles` like `".2"`. Changes in 2999.5.0.0 --------------------- A major re-write occured; these are the highlights: * Re-write parsing and printing of Dot code using the new `ParseDot` and `PrintDot` classes. This should finally fix all quoting issues, as well as leaving `Show` as the code representation for hacking purposes. As part of this, the `Data.GraphViz.ParserCombinators` module has been moved to `Data.GraphViz.Types.Parsing`. * Re-write the various `Dot*` datatypes in `Data.GraphViz.Types`. Sub-graphs/clusters are now their own entity rather than being part of `DotNode` and the Node ID type is now a type parameter rather than being just `Int`. Sub-graphs/clusters can now also be parsed. * The various conversion functions in `Data.GraphViz` now come in two flavours: the unprimed versions take in a `Bool` indicating if the graph is directed or not; the primed versions attempt to automatically detect this. * Add cluster support for the graph augmentation functions, **as requested by Nikolas Mayr**. * Allow custom arrow types as supported by GraphViz; **as requested by Han Joosten**. * Fixed a bug in HSV-style `Color` values where `Int` was used instead of `Double`; **spotted by Michael deLorimier**. * Properly resolved the situation initially spotted by Neil Brown: Matthew Sackman was following Dot terminology for an edge `a -> b` when using _head_ for `b` and _tail_ for `a` (this is presumably because the head/tail of the arrow are at those nodes). `DotEdge` now uses _from_ and _to_ avoid ambiguity; the various `Attribute` values still follow upstream usage. Changes in 2999.1.0.2 --------------------- * Fix a bug **spotted by Srihari Ramanathan** where `Color` values were double-quoted. Changes in 2999.1.0.1 --------------------- * The `Color` `Attribute` should take `[Color]`, not just a single `Color`. Changes in 2999.1.0.0 --------------------- * Stop using `Either` for composite `Attributes` and use a custom type: this avoids problems with the `Show` instance. Changes in 2999.0.0.0 --------------------- * Fixed a bug where the Show instance and read function for `DotEdge` had the from/to nodes the wrong way round. This was not immediately noticed since the `Graph` to `DotGraph` functions created them the wrong way round, so for those users who only used these this was not apparent. **Spotted by Neil Brown.** * Greatly improved `Attribute` usage: almost all attributes are now covered with allowed values. * Extend DotGraph to include whether a graph is strict or not and if it has an ID. Also move the directedGraph field. * Make `Dot` refer to the actual dot command and `DotArrow` refer to the `ArrowType` (rather than `DotCmd` and `Dot` as before). * Make the `Data.GraphViz.ParserCombinators` module available to end users again, but not re-exported by `Data.GraphViz`; it has a warning message up the top not to be used. It is there purely for documentative purposes. * Use [extensible-exceptions] so that `base-3.x` is once again supported. [extensible-exceptions]: http://hackage.haskell.org/package/extensible-exceptions * Follow the [Package Versioning Policy] rather than using dates for versions. [Package Versioning Policy]: http://www.haskell.org/haskellwiki/Package_versioning_policy Changes in 2009.5.1 ------------------- * New maintainer: Ivan Lazar Miljenovic. * Support `polyparse >= 1.1` (as opposed to `< 1.3`) * Require `base == 4.*` (i.e. `GHC 6.10.*`) due to new exception handling. * Include functions from [Graphalyze-0.5] for running GraphViz commands, etc. [Graphalyze-0.5]: http://hackage.haskell.org/package/Graphalyze-0.5 * Module re-organisation. * The `Data.GraphViz.ParserCombinators` module is no longer available to end users. * Improved Haddock documentation. Changes in 2008.9.20 -------------------- * Differentiate between undirected and directed graphs (previously only directed graphs were supported). * Clustering support was added. Older versions -------------- For versions of graphviz older than `2008.9.20`, the exact differences between versions is unknown. graphviz-2999.20.2.0/README.md0000644000000000000000000000350114536315671013517 0ustar0000000000000000 The graphviz Library ==================== The _graphviz_ library provides bindings to the [Graphviz] graph visualisation suite of tools for the purely functional programming language [Haskell]. It can be downloaded from [HackageDB] or - if you have [cabal-install] - installing it is as simple as: ~~~~~~~~~~~~~~~~~~~~ {.bash} cabal update cabal install graphviz ~~~~~~~~~~~~~~~~~~~~ [Graphviz]: http://www.graphviz.org/ [Haskell]: http://haskell.org/ [HackageDB]: http://hackage.haskell.org/package/graphviz [cabal-install]: http://haskell.org/haskellwiki/Cabal-Install Library features ---------------- Main features of the graphviz library include: * Almost complete coverage of all Graphviz attributes and syntax. * Support for specifying clusters. * The ability to use a custom node type. * Functions for running a Graphviz layout tool with all specified output types. * The ability to not only generate but also parse Dot code with two options: strict and liberal (in terms of ordering of statements). * Functions to convert [FGL] graphs and other graph-like data structures to Dot code - including support to group them into clusters - with a high degree of customisation by specifying which attributes to use and limited support for the inverse operation. * Round-trip support for passing an [FGL] graph through Graphviz to augment node and edge labels with positional information, etc. [FGL]: http://web.engr.oregonstate.edu/~erwig/fgl/haskell/ graphviz is free software licensed under a [3-Clause BSD License]. \(C\) 2008 [Matthew Sackman](http://www.wellquite.org/) \(C\) 2008 - onwards [Ivan Lazar Miljenovic](http://ivanmiljenovic.wordpress.com/) [3-Clause BSD License]: http://www.opensource.org/licenses/bsd-license.php For more information, feel free to [email](mailto:Ivan.Miljenovic+graphviz@gmail.com) me. graphviz-2999.20.2.0/FAQ.md0000644000000000000000000005773514536315671013213 0ustar0000000000000000 Fortuitously Anticipated Queries (FAQ) ====================================== Note that to distinguish it from [Graphviz], the library shall be henceforth referred to as _graphviz_. Graphviz vs _graphviz_ ---------------------- ### What is the difference between Graphviz and _graphviz_? ### [Graphviz] is an open source library and collection of utility programs using that library to visualise [graphs] (which are specified using the [Dot] language). _graphviz_ is a library for the purely functional programming language [Haskell] that provides "bindings" to Graphviz's programs. It does so by allowing programmers to specify the layout of the graph and then converts that to Dot code before calling the appropriate program to perform the visualisation. [Graphviz]: http://www.graphviz.org/ [graphs]: http://en.wikipedia.org/wiki/Graph_theory [Dot]: http://www.graphviz.org/doc/info/lang.html [Haskell]: http://haskell.org/ ### Why should I use graphviz over one of the other Haskell Graphviz libraries? ### Various Haskell libraries have support for Graphviz to one extent or another; however _graphviz_ has the most comprehensive support available out of all of them: * There are [four different representations] of Dot graphs: 1. Canonical, which provides a clean separated definition of a Dot graph (that matches the former layout of `dot -Tcanon`). 2. Generalised, which allows statements to be in any order. 3. A graph-based one that allows manipulation of the Dot graph. 4. A monadic interface for embedding relatively static graphs in Haskell. There are also conversion functions between them. [four different representations]: #whats-the-difference-between-the-different-dotgraph-types * The ability to parse and generate most aspects of Dot [syntax] and [attributes]. This includes taking into account escaping and quoting rules where applicable. [syntax]: http://graphviz.org/doc/info/lang.html [attributes]: http://graphviz.org/doc/info/attrs.html * The ability to use a custom node type for Dot graphs. * Support for all stated layout algorithm programs and all specified [output formats] as well as the ability to use custom programs, etc. [output formats]: http://www.graphviz.org/doc/info/output.html * Functions to convert [FGL] graphs and other graph-like structures (albeit not as nicely) to and from the internal Dot representations. In future, this will be expanded to a much larger range of graph-like values once a suitable abstraction is available. [FGL]: http://web.engr.oregonstate.edu/~erwig/fgl/haskell/ * The ability to augment Dot and FGL graphs with positioning information by round-trip passing through Graphviz. * Pure Haskell implementations of `dot -Tcanon` and `tred`. * _graphviz_ is continually being worked upon and expanded to better suit/match the requirements of Graphviz, to improve performance and to make it easier for the programmer to use. ### Is the API of _graphviz_ stable? ### For the most part, yes: the only items that are likely to change in the future are those with bugs/errors or if a radically better way of doing things is found. For most uses, however, the API should not change for the foreseeable future. Note that _graphviz_'s version numbers follow the [package versioning policy]; this means that you can immediately tell when the API has had a backwards-incompatible change by comparing the first two elements of the version. However, these changes won't always affect most users. [package versioning policy]: http://www.haskell.org/haskellwiki/Package_versioning_policy ### What aspects of Dot syntax and attributes are covered? ### It's easier to state which aspects of Dot [syntax] and [attributes] _aren't_ covered: #### Overall syntax items not covered #### * Cannot specify a sub-graph as an end point in an edge; * Comments, pre-processor lines and split lines are (currently) not supported within HTML-like labels. * _graphviz_ only uses UTF-8 encoding for printing and parsing (whereas Graphviz allows Latin1 encoding with the `charset` attribute). * Graphviz is more liberal in accepting "invalid" values (e.g. accepting a floating-point value when only integer values are meant to be accepted); _graphviz_ is more strict in this aspect (and will indeed throw an exception if it cannot parse something properly). * No extensions (e.g. postscript-specific attributes) are available. #### Attribute and value items not covered #### * The global `orientation` attribute is not defined; however its behaviour is duplicated by the `rotate` attribute. * The deprecated `overlap` algorithms have not been defined, and the ability to specify an integer prefix for use with the `fdp` layout tool is not available. * The deprecated `shapefile` attribute is not available; instead, you should specify the file on the command line. * The deprecated `z` attribute is not available; use the optional third dimension for the `pos` attribute instead. * Only polygon-based `shape`s are available (i.e. no custom shapes as yet). * The `charset` attribute is not available as _graphviz_ assumes that all Dot graphs will be in UTF-8 for simplicity; if Latin1-encoded graphs need to be parsed then you shall need to do all I/O for them by hand. * `colorscheme` attributes _are_ parsed, but the behaviour is not quite the same: consider the following minimal Dot graph: ~~~~~ {.dot} digraph { a [ style=filled, fillcolor=gray, colorscheme=svg ] } ~~~~~ Despite the fact that the color is specified before the colorscheme, Graphviz will use that colorscheme to parse the color (as an SVG gray differs from the X11 gray); _graphviz_, however, will use the default colorscheme of `x11` to parse the color, and **then** set the colorscheme to be `svg` (despite it not being used after it is set). #### Available items of note #### There are a few items of note that are available that are worthy of special note (as they may not be immediately obvious from the generated documentation): * _graphviz_ is able to parse (but not print) the following special aspects of specifying edges in Dot code: - The `node:port` method of specifying of head/tail `portPos` values. - Stating multiple edges with common interior nodes (e.g. `a -> b -> c`). - Stating edges with a grouping of nodes (e.g. `a -> {b c}`). * Sub-graphs are specified as being clusters when the subgraph name starts with either `"cluster"` or `"cluster_"`; note that this prefix is removed when determining the subraph's name for the internal datatypes. * Anonymous subgraphs (where not even the `subgraph` keyword is specified) are also parseable. * HTML-like and record labels are available, and feature proper escaping/unescaping when printing/parsing. * Other syntactic issues are taken care of for you automatically (such as escaping/unescaping quotation marks). Even newlines are automatically escaped (but not unescaped) for you, defaulting to centered lines. Getting _graphviz_ and more documentation ----------------------------------------- ### Where can I obtain _graphviz_? ### The best place to get _graphviz_ is from its [HackageDB] page. [HackageDB]: http://hackage.haskell.org/package/graphviz ### Where can I find the API documentation for _graphviz_? ### Also on its [HackageDB] page. ### Is it safe to install and use _graphviz_ from its git repository? ### No; unlike other projects I make no guarantees as to the stability of the live version of _graphviz_. Whilst the [git] [repository] is _usually_ stable, it's often in a state of flux and at times patches that break the repository are recorded (when it's simpler/cleaner to break one patch into several smaller patches). [git]: http://git-scm.com/ [repository]: https://github.com/ivan-m/graphviz/ ### How is _graphviz_ licensed? ### _graphviz_ is licensed under a [3-Clause BSD License] (note that the ColorBrewer Color Schemes found in `Data.GraphViz.Attributes.Colors.Brewer` are covered under [their own license](http://graphviz.org/doc/info/colors.html#brewer_license)). [3-Clause BSD License]: http://www.opensource.org/licenses/bsd-license.php Simplistically, this means that you can do whatever you want with _graphviz_ as long as you cite both myself and [Matthew Sackman] (the original author) as being the authors of _graphviz_. However, I would appreciate at least an [email] letting me know how _graphviz_ is being used. [Matthew Sackman]: http://www.wellquite.org/ [email]: mailto:Ivan.Miljenovic@gmail.com ### Where can I find more information on _graphviz_? ### From its [home page]. [home page]: http://projects.haskell.org/graphviz/ ### Are there any tutorials on how to use _graphviz_? ### A basic tutorial on [how to visualise graph-like data](http://ivanmiljenovic.wordpress.com/2011/10/16/graphviz-in-vacuum/) is available; more will come if people ask for it. ### What other packages use _graphviz_? ### This is a list of all known packages that use _graphviz_: if you know of any others please let me know and I'll add it to the list. * [Graphalyze](http://hackage.haskell.org/package/Graphalyze) * [SourceGraph](http://hackage.haskell.org/package/SourceGraph) ### What is the history of _graphviz_? ### _graphviz_ was originally written by [Matthew Sackman] (if you want his reasons for doing so, you'll have to ask him yourself) with the first known release being on 10 July, 2008. In 2008 I (Ivan Miljenovic) needed a library that provided bindings to Graphviz with clustering support; at the time _graphviz_ was the most fully featured and closest to what I wanted, so I submitted a patch that provided support for both clustering and undirected graphs. In April 2009, Matthew wanted to step down from maintaining _graphviz_ and asked if I wanted to take over. Since then the library has been almost completely re-written with greatly improved coverage of the Dot language and extra features. However, the original outline of the library still remains. Using _graphviz_ ---------------- ### Can I start using _graphviz_ without knowing anything about Graphviz? ### You can, but if you want to start doing anything more advanced then you should be reading Graphviz's documentation as well as _graphviz_'s. This is because the layout and design of _graphviz_ is heavily based upon the Dot language and the various [attributes] that Graphviz supports. ### Can I just use _graphviz_ without reading its documentation? ### You should _at least_ read the various messages about possible ambiguities, etc. at the top of each module and for the attributes you use before you use _graphviz_. ### Do I need to have Graphviz installed to use _graphviz_? ### Technically, no if you're only dealing with the Dot language aspects. However, usage of the functions in the `Commands` module, or the augmentation of pretty-printing functions in the GraphViz module _do_ require Graphviz to be installed. ### Why didn't you use FFI to bind to the Graphviz library? ### Because I just kept working where [Matthew Sackman] left off and it was already using Graphviz's tools rather than the actual library. However, most other language bindings (for Python, Perl, etc.) seem to do the same: generate Dot code and pass that to the relevant tool. This, however, does provide a fortunate side effect where the ability to print and parse Dot code means that _graphviz_ can be used for more than just visualising graphs created solely in Haskell: it can also import pre-defined graphs, or else generate Dot code for use with other tools. ### What's the difference between the different DotGraph types? ### _graphviz_ has four different "implementations" of Dot code: **Canonical:** : matches the (former) output of `dot -Tcanon`. Recommended for use when converting existing data into Dot (especially with the `graphElemsToDot` function in `Data.GraphViz`). **Generalised:** : most closely matches the layout of actual Dot code, as such this is preferred when parsing in arbitrary Dot graphs. Also useful in cases where you want to use the common Graphviz "hack" of specifying global attributes that don't apply to sub-graphs _after_ the sub-graphs in question. **Graph:** : provides common graph operations on Dot graphs, based upon those found in the [FGL]. **Monadic:** : a nicer way of defining relatively static Dot graphs to embed within Haskell code, etc. Loosely based (with permission!) upon Andy Gill's [dotgen] library. [dotgen]: http://hackage.haskell.org/package/dotgen ### What's the best way to parse Dot code? ### Use the `parseDotGraph` function (rather than the general parsing functions that are available) to parse your Dot code: this is will strip out comments and pre-processor lines and join together split lines (if any of these remain the parser will fail). Also, if you are not sure what the type of the nodes are, use either String or else the `GraphID` type as it explicitly caters for both Strings and numbers (whereas just assuming it being a String will result in numbers being stored internally as a String). Unless you are very sure of the representation of the Dot code you have been provided, you should parse in any Dot code as the `Generalised.DotGraph` type. Afterwards you can use `FromGeneralisedDot` to convert to whichever representation you prefer. ### There are too many attributes!!! Which ones should I use? ### The `Data.GraphViz.Attributes` module contains a cut-down list of recommended and commonly used attributes. The entire list of attributes can be found in `Data.GraphViz.Attributes.Complete`. In particular, the following attributes are **not** recommended for use: * `Color` for anything except edge colours or gradients for nodes, clusters and graphs when using Graphviz >= 2.29.0 (and if you must, the border colour for a node). * `ColorScheme`: just stick with X11 colours. * `Comment`: pretty useless. Enough said. ### Can I use any attribute wherever I want? ### No: attributes are all defined in one big datatype for the sake of simplicity, but not all attributes are valid in all places. Read the documentation (either for Graphviz or _graphviz_) to determine which is suitable where. ### How can I use _graphviz_ to visualise non-FGL graphs? ### The `graphElemsToDot` function allows you to visualise any graph for which you can specify a list of labelled nodes and a list of labelled edges. ### How can I use/process multiple graphs like Graphviz does? ### At one stage, _graphviz_ supported dealing with lists of `DotGraph`s; however, it was found to be faster to deal with each graph individually rather than try to get Graphviz to deal with them all in one go. In future, once the problem causing this has been tracked down and fixed this feature will be returned. ### How can I use custom datatypes for node IDs? ### The important thing here is to ensure that your custom datatype has defined instances of `PrintDot` and `ParseDot`. Probably the easiest way of doing this is to have functions that convert between your type and `String` or `Text` and let graphviz determine how to print and parse those. Here is an example of a more difficult type that should be printed like `"1: Foo"`: ~~~~~~~~~~~~~~~~~~~~ {.haskell} data MyType = MyType Int String instance PrintDot MyType where unqtDot (MyType i s) = unqtDot i <> colon <+> unqtDot s -- We have a space in there, so we need quotes. toDot = doubleQuotes . unqtDot instance ParseDot MyType where parseUnqt = MyType <$> parseUnqt <* character ':' <* whitespace1 <*> parseUnqt -- Has at least one space, so it will be quoted. parse = quotedParse parseUnqt ~~~~~~~~~~~~~~~~~~~~ Things to note from this example: * Whilst `PrintDot` and `ParseDot` have default definitions for `toDot` and `parse`, they assume the datatype doesn't need quotes; as such if the value will [need quoting](http://www.graphviz.org/doc/info/lang.html), then you should do so explicitly. * It is better to use the `PrintDot` instances for common types such as `Int` and `String` rather than using the pretty-printers inbuilt conversion functions (`int`, `text`, etc.) to ensure that quotations, etc. are dealt with correctly. * Be as liberal as you can when parsing, especially with whitespace: when printing only one space is used, yet when parsing we use the `whitespace1` parsing combinator that will parse all whitespace characters (but it must consume _at least_ one; there is a variant that does not need to parse any). ### When parsing Dot code, do I have to worry about the case? ### Not at all: _graphviz_'s parser is case-insensitive; however, the correct case is checked first so there is a slight degradation in performance when the wrong case is used. ### How do I set portPos values for nodes in edges? ### Graphviz allows you to specify edges such as `from:a -> to:b` where the nodes "from" and "to" are defined with either `RecordLabel` or `Html.Label` labels and have different sections; the edge is then drawn from the "a" section of the "from" node to the "b" section of the "to" node. Whilst _graphviz_ can parse this, you can't define this yourself; instead, do it the manual way: ~~~~~~~~~~~~~~~~~~~~ {.haskell} DotEdge "from" "to" True [ TailPort (LabelledPort (PN "a") Nothing) , HeadPort (LabelledPort (PN "b") Nothing) ] ~~~~~~~~~~~~~~~~~~~~ I realise that doing this manually isn't as convenient, but I am open to suggestions on how this can be improved. Note where `TailPort` and `HeadPort` are used; the next question explains this. ### Is there anything else I should know? ### A few other things of note that you should know about: * For an edge `a -> b`, Graphviz terms "a" to be the _tail_ node and "b" to be the _head_ node. * When creating `GraphID` values for the graphs and sub-graphs, you should ensure that they won't clash with any of the `nodeID` values when printed to avoid possible problems. * It is a good idea to have unique IDs for sub-graphs to ensure that global attributes are applied only to items in that sub-graph and so that clusters aren't combined (it took me a _long_ time to find out that this was the case). * You should specify an ID for the overall graph when outputting to a format such as SVG as it becomes the title of that image. * Graphviz allows a node to be "defined" twice with different attributes; in practice they are combined into one node. Running Dot code through `dot -Tcanon` before parsing removes this problem. * Several attributes are defined with taking a list of items; all of these assume that the provided lists are non-empty (sub-values are a different story). * If a particular Dot graph is not parseable, the parser throws an error rather than failing gracefully. Design Decisions ---------------- ### Why does _graphviz_ use Polyparse rather than Parsec? ### Short answer: because _graphviz_ was already using [Polyparse] when I started working on it (and I hadn't done any parsing before so I had no preference either way). [Polyparse]: http://www.cs.york.ac.uk/fp/polyparse/ Longer answer: Polyparse has several advantages I feel over [Parsec]: * Simpler types. * Avoids the whole "but Parsec-3 is slower than Parsec-2" debate (with its associated baggage/problems). * Few inbuilt combinators: since there is no inbuilt `character` parsing combinator, there are no problems with _graphviz_ using its own case-less one. * [Easier backtracking](http://www.cs.york.ac.uk/fp/polyparse/#how) [Parsec]: http://hackage.haskell.org/package/parsec ### Why do you have four different representations of Dot graphs? ### _graphviz_ has [four different representations] of Dot graphs. Apart from the reasons given before, the canonical implementation was the original representation, whereas the generalised one was only introduced in the 2999.8.0.0 release and the other two in the 2999.12.0.0 release. Note, however, that I was thinking of adding something like the generalised implementation back around the time of the [2999.0.0.0 release](http://www.haskell.org/pipermail/haskell-cafe/2009-July/064436.html), yet [people didn't like the idea](http://www.haskell.org/pipermail/haskell-cafe/2009-July/064442.html). The graph-based implementation was added solely so I could write an (as-yet finished) tutorial, and thought others might find it useful. The monadic implementation came about as an attempt to encourage more people to use _graphviz_ rather than other libraries such as [dotgen], and I thought a nicer way of writing Dot graphs might help (the initial plans involved complicated type-hackery to try and almost make it a DSL for actual Dot code; however it ended up being too complicated and unwieldy). ### Why are only FGL graphs supported? ### Love them or hate them, [FGL] currently provides the best graph datatype and library available for Haskell at this time. As such, if any one graph type had to be chosen to have conversion functions written for it then FGL is the best option. Furthermore, I needed FGL graph support (which is the much more important reason!). ### Why are the version numbers so high? ### To make sure the latest release has the highest version number: Matthew Sackman originally made releases with date-based versioning, but when I switched to using the [package versioning policy] I had to change this. I could have started with 2010.x.y.z or so, but at the time I had initial hopes of introducing compatibility with other graphs (not just [FGL] ones) soon and wanted to make that the 3000.0.0.0 release; however that has not yet come to pass. ### Why do you use the American spelling of colour in _graphviz_? ### Because that's how Graphviz spells it, and I was following upstream to avoid confusion. Bugs, Feature Requests and Development -------------------------------------- ### Do you have any future plans for _graphviz_? ### Yes, I do! See the TODO file for more information. ### Does _graphviz_ have a test suite? ### Yes, there is, using the in-built support for test suites in Cabal: ~~~~~~~~~~~~~~~~~~~~ {.bash} cabal install graphviz --enable-tests ~~~~~~~~~~~~~~~~~~~~ Then run the `graphviz-testsuite` executable. This test suite uses [QuickCheck] to ensure that _graphviz_ can parse the Dot code it generates (as well as a few other things). Note that it isn't perfect: there are no guarantees that the Dot graphs that are generated are indeed valid, and those more extensive tests are not yet available. [QuickCheck]: http://hackage.haskell.org/package/QuickCheck Furthermore, you can do more controlled testing to try and track down the source of a bug as the above flag will also expose several testing modules which give you access to the various tests used as well as the `Arbitrary` instances for use with [QuickCheck]. For proper testing of real-life Dot code, there is also the `TestParsing.hs` script that comes in the _graphviz_ tarball (but is not installed). Once you have _graphviz_ installed you can just run this script, passing it any files containing Dot graphs you wish to test. It will attempt to parse each Dot graph as a `Generalised.DotGraph`, and then test to see if the canonicalised form is parseable as a `DotGraph`. ### I've found a bug! ### Oh-oh... please file a report at the GitHub [repository] to tell me the specifics of what you were doing (including the Dot file in question if it's a parsing problem) and I'll get right on it. ### I have a feature request. ### Is it in the TODO? If not, file an issue at the GitHub [repository] and I'll consider implementing it (depending on time and how well I think it will fit in the overall library). ### I want to help out with developing _graphviz_. ### Great! Whether you have a specific feature in mind or want to help clear the TODO list, please create a pull-request on the GitHub [repository]. ### What is the purpose of the AttributeGenerator.hs file? ### Graphviz has a large number of attributes. Rather than try to edit everything manually each time I want to change how I use the large `Attribute` datatype, the AttributeGenerator script generates the datatype, instances, etc. for me. graphviz-2999.20.2.0/utils/AttributeGenerator.hs0000755000000000000000000020073114535166704017555 0ustar0000000000000000#!/usr/bin/runhaskell {- | Module : AttributeGenerator Description : Definition of the Graphviz attributes. Copyright : (c) Ivan Lazar Miljenovic License : 3-Clause BSD-style Maintainer : Ivan.Miljenovic@gmail.com This module is a stand-alone that generates the correct code for Data.GraphViz.Attributes. -} module Data.GraphViz.AttributeGenerator where import Text.PrettyPrint import Data.List(transpose) import Data.Maybe(catMaybes, isJust, fromJust) import Control.Monad(liftM) import System.Environment(getArgs) type Code = Doc -- If any args are passed in, then generate the Arbitrary instance -- instead of the definition. main :: IO () main = do args <- getArgs let f = if null args then genCode else genArbitrary print $ f att where att = AS { tpNm = text "Attribute" , atts = attributes } genCode :: Atts -> Doc genCode att = vsep $ map ($att) cds where cds = [ createDefn , createAlias , nameAlias , showInstance , parseInstance , usedByFunc "Graphs" forGraphs , usedByFunc "Clusters" forClusters , usedByFunc "SubGraphs" forSubGraphs , usedByFunc "Nodes" forNodes , usedByFunc "Edges" forEdges , sameAttributeFunc , defValueFunc , validUnknownFunc ] genArbitrary :: Atts -> Doc genArbitrary = arbitraryInstance -- ----------------------------------------------------------------------------- -- Defining data structures data Atts = AS { tpNm :: Code , atts :: [Attribute] } data Attribute = A { cnst :: Code , name :: Code , parseNames :: [Code] , valtype :: VType , parseDef :: Maybe Code , defValue :: Maybe Code , forGraphs :: Bool , forClusters :: Bool , forSubGraphs :: Bool , forNodes :: Bool , forEdges :: Bool , comment :: Doc } makeAttr :: Constructor -> [Name] -> UsedBy -> VType -> Maybe Default -- Used when parsing the field -> Maybe Default -- Used as a default value if necessary -> Maybe Default -> Maybe Minimum -> Maybe Comment -> Attribute makeAttr c ns u v df d fd m cm = A { cnst = text c , name = head ns' , parseNames = ns' , valtype = v -- just in case need to do fancy -- stuff , parseDef = liftM text df , defValue = liftM text d , forGraphs = isFor 'G' , forClusters = isFor 'C' || forSG , forSubGraphs = forSG , forNodes = isFor 'N' , forEdges = isFor 'E' , comment = cm' } where ns' = map text ns isFor f = f `elem` u forSG = isFor 'S' df' = if v == Bl then Just "'True'" else fmap ( \ t -> '\'' : t ++ "'") df mDoc (f,fc) = f <> colon <+> text fc addF f = fmap (\ dc -> (wrap (char '/') (text f), dc)) cm' = hsep . punctuate semi . map mDoc $ catMaybes [ addF "Valid for" (Just u) , addF "Default" fd , addF "Parsing Default" df' , addF "Minimum" m , addF "Notes" cm ] type Constructor = String type Name = String type UsedBy = String -- should only contain subset of "ENGCS" type Default = String type Minimum = String type Comment = String data VType = Dbl | Integ | Strng | EStrng | Bl | Cust String deriving (Eq, Ord, Show, Read) vtype :: VType -> Doc vtype Dbl = text "Double" vtype Integ = text "Int" vtype Strng = text "Text" vtype EStrng = text "EscString" vtype Bl = text "Bool" vtype (Cust t) = text t vtypeCode :: Attribute -> Code vtypeCode = vtype . valtype -- ----------------------------------------------------------------------------- createDefn :: Atts -> Code createDefn att = hdr $+$ constructors $+$ derivs where hdr = text "data" <+> tpNm att constructors = nest tab . asRows . firstOthers equals (char '|') . (++ [defUnknown]) . map createDf $ atts att derivs = nest tab $ text "deriving (Eq, Ord, Show, Read)" createDf a = [cnst a <+> vtypeCode a , if isEmpty cm then empty else text "-- ^" <+> cm ] where cm = comment a defUnknown = [ unknownAttr <+> unknownNameAlias <+> vtype Strng , text "-- ^ /Valid for/: Assumed valid for all; the fields are 'Attribute' name and value respectively." ] createAlias :: Atts -> Code createAlias att = text "type" <+> tp <> char 's' <+> equals <+> brackets tp where tp = tpNm att -- The Atts value isn't used; this is just to make it have the same -- type as the other code-generating functions. nameAlias :: Atts -> Code nameAlias _ = cmnt $$ (text "type" <+> unknownNameAlias <+> equals <+> vtype Strng) where cmnt = text "-- | The name for an" <+> unknownAttr <> text "; must satisfy " <+> quotes validUnknownName <> text "." unknownNameAlias :: Code unknownNameAlias = text "AttributeName" showInstance :: Atts -> Code showInstance att = hdr $+$ insts' where hdr = text "instance" <+> text "PrintDot" <+> tpNm att <+> text "where" var = char 'v' sFunc = text "unqtDot" insts = asRows . (++ [unknownInst]) . map mkInstance $ atts att mkInstance a = [ sFunc <+> parens (cnst a <+> var) , equals <+> text "printField" <+> doubleQuotes (name a) <+> var ] unknownInst = [ sFunc <+> parens (unknownAttr <+> char 'a' <+> var) , equals <+> text "toDot" <+> char 'a' <+> text "<> equals <>" <+> text "toDot" <+> var ] insts' = nest tab $ vsep [ insts , text "listToDot" <+> equals <+> text "unqtListToDot" ] parseInstance :: Atts -> Code parseInstance att = hdr $+$ nest tab fns where hdr = text "instance" <+> text "ParseDot" <+> tpNm att <+> text "where" fn = pFunc <+> equals <+> (text "stringParse" <+> parens (text "concat" <+> ops) $$ text "`onFail`" $$ pUnknown) fns = vsep [ fn , text "parse" <+> equals <+> pFunc , text "parseList" <+> equals <+> text "parseUnqtList" ] ops = flip ($$) rbrack . asRows . firstOthers lbrack comma . map return . map parseAttr $ atts att pFunc = text "parseUnqt" pType b a | valtype a == Bl = pFld <> text "Bool" <+> cnst a | isJust $ parseDef a = pFld <> text "Def" <+> cnst a <+> fromJust (parseDef a) | otherwise = pFld <+> cnst a where pFld = text "parseField" <> if b then char 's' else empty parseAttr a = case map doubleQuotes $ parseNames a of [n] -> pType False a <+> n ns -> pType True a <+> docList ns unknownName = text "attrName" pUnknown = text "do" <+> ( (unknownName <+> text "<- stringBlock") $$ (text "liftEqParse" <+> (parens (text "\"" <> unknownAttr <+> text "(\"" <+> text "++ T.unpack" <+> unknownName <+> text "++ \")\"") $$ parens (unknownAttr <+> unknownName) ) ) ) arbitraryInstance :: Atts -> Code arbitraryInstance att = hdr $+$ fns where hdr = text "instance" <+> text "Arbitrary" <+> tpNm att <+> text "where" fns = nest tab $ vsep [aFn, sFn] aFn = aFunc <+> equals <+> text "oneof" <+> ops ops = flip ($$) rbrack . asRows . firstOthers lbrack comma . (++ [[aUnknown]]) . map (return . arbAttr) $ atts att aFunc = text "arbitrary" arbAttr a = text "liftM" <+> cnst a <+> arbitraryFor' a sFn = asRows . (++ [sUnknown]) . map shrinkAttr $ atts att sFunc = text "shrink" var = char 'v' shrinkAttr a = [ sFunc <+> parens (cnst a <+> var) , equals <+> text "map" <+> cnst a , dollar <+> shrinkFor (valtype a) <+> var ] aUnknown = text "liftM2" <+> unknownAttr <+> parens (text "suchThat" <+> text "arbIDString" <+> validUnknownName) <+> arbitraryFor Strng sUnknown = [ sFunc <+> parens (unknownAttr <+> char 'a' <+> var) , equals <+> text "liftM2" <+> unknownAttr , parens (text "liftM" <+> parens (text "filter" <+> validUnknownName) <+> shrinkFor Strng <+> char 'a') <+> parens (shrinkFor Strng <+> var) ] validUnknownName :: Code validUnknownName = text "validUnknown" validUnknownFunc :: Atts -> Code validUnknownFunc att = cmnt $$ asRows [tpSig, def] $$ whClause where var = text "txt" setVar = text "names" cmnt = text "-- | Determine if the provided 'Text' value is a valid name" <+> text "for an '" <> unknownAttr <> text "'." tpSig = [ validUnknownName , colon <> colon <+> text "AttributeName -> Bool" ] def = [ validUnknownName <+> var , equals <+> (text "T.toLower" <+> var <+> text "`S.notMember`" <+> setVar $$ text "&&" <+> text "isIDString" <+> var) ] whClause = nest tab $ text "where" $$ nest tab setDef setDef = setVar <+> equals <+> mkSet mkSet = parens (text "S.fromList . map T.toLower" $$ dollar <+> setList) $$ text "`S.union`" $$ text "keywords" setList = flip ($$) rbrack . asRows . firstOthers lbrack comma . flip (++) [[doubleQuotes (text "charset") <+> text "-- Defined upstream, just not used here."]] . map ((:[]) . doubleQuotes) . concatMap parseNames $ atts att arbitraryFor :: VType -> Doc arbitraryFor = text . bool "arbitrary" "arbList" . isListType arbitraryFor' :: Attribute -> Doc arbitraryFor' = arbitraryFor . valtype shrinkFor :: VType -> Doc shrinkFor = text . bool "shrink" "nonEmptyShrinks" . isListType -- Some types are aliases for lists. isListType :: VType -> Bool isListType (Cust ('[':_)) = True isListType (Cust "ColorList") = True isListType _ = False usedByFunc :: String -> (Attribute -> Bool) -> Atts -> Code usedByFunc nm p att = cmnt $$ asRows (tpSig : trs ++ [fls]) where nm' = text nm dt = tpNm att cmnt = text "-- | Determine if this '" <> dt <> text "' is valid for use with" <+> nm' <> dot tpSig = [ fn , colon <> colon <+> dt <+> text "->" <+> text "Bool" ] fn = text "usedBy" <> nm' tr = text "True" trs = map aTr as' ++ [unknownATr] fl = text "False" fls = [ fn <+> char '_' , equals <+> fl ] as' = filter p $ atts att aTr a = [ fn <+> cnst a <> braces empty , equals <+> tr ] unknownATr = [ fn <+> unknownAttr <> braces empty , equals <+> tr ] sameAttributeFunc :: Atts -> Code sameAttributeFunc att = cmnt $$ asRows (tpSig : stmts ++ [unknownAtr, rst]) where cmnt = text "-- | Determine if two '" <> dt <> text "s' are the same type of '"<> dt <> text"'." sFunc = text "sameAttribute" dt = tpNm att tpSig = [ sFunc , char ' ' -- first arg, for some reason won't line up -- properly if its empty , empty -- second arg , colon <> colon <+> dt <+> text "->" <+> dt <+> text "->" <+> text "Bool" ] stmts = map sf $ atts att sf a = [ sFunc , cnst a <> braces empty , cnst a <> braces empty , equals <+> tr ] tr = text "True" catchAll = char '_' unknownAtr = [ sFunc , parens $ unknownAttr <+> text "a1" <+> catchAll , parens $ unknownAttr <+> text "a2" <+> catchAll , equals <+> text "a1" <+> equals <> equals <+> text "a2" ] rst = [ sFunc , catchAll , catchAll , equals <+> text "False" ] defValueFunc :: Atts -> Code defValueFunc att = cmnt $$ asRows (tpSig : stmts ++ [unknownAtr]) where cmnt = text "-- | Return the default value for a specific" <+> quotes dt <+> text "if possible; graph/cluster values are preferred" <+> text "over node/edge values." dFunc = text "defaultAttributeValue" dt = tpNm att tpSig = [ dFunc , colon <> colon <+> dt <+> text "->" <+> text "Maybe" <+> dt ] stmts = map sf . filter (isJust . defValue) $ atts att sf a = [ dFunc <+> cnst a <> braces empty , equals <+> text "Just" <+> text "$" <+> cnst a <+> fromJust (defValue a) ] unknownAtr = [ dFunc <+> char '_' , equals <+> text "Nothing" ] -- ----------------------------------------------------------------------------- -- Helper functions -- Size of a tab character tab :: Int tab = 2 firstOthers :: Doc -> Doc -> [[Doc]] -> [[Doc]] firstOthers _ _ [] = [] firstOthers f o (d:ds) = (f : d) : map ((:) o) ds wrap :: Doc -> Doc -> Doc wrap w d = w <> d <> w vsep :: [Doc] -> Doc vsep = vcat . punctuate newline where newline = char '\n' asRows :: [[Doc]] -> Doc asRows as = vcat $ map padR asL where asL = map (map (\d -> (d, docLen d))) as cWidths = map (maximum . map snd) $ transpose asL shiftLen rls = let (rs,ls) = unzip rls in zip rs (0:ls) padR = hsep . zipWith append (0 : cWidths) . shiftLen append l' (d,l) = hcat (repl (l' - l) space) <> d repl n xs | n <= 0 = [] | otherwise = replicate n xs -- A really hacky thing to do, but oh well... -- Don't use this for multi-line Docs! docLen :: Doc -> Int docLen = length . render docList :: [Doc] -> Doc docList = brackets . hsep . punctuate comma dot :: Doc dot = char '.' -- ----------------------------------------------------------------------------- -- The actual attributes -- Don't edit this value directly; edit the table below instead. attributes :: [Attribute] attributes = [ -- BEGIN RECEIVE ORGTBL Attributes makeAttr "Damping" ["Damping"] "G" (Dbl) Nothing (Just "0.99") (Just "@0.99@") (Just "@0.0@") (Just "'Neato' only"), makeAttr "K" ["K"] "GC" (Dbl) Nothing (Just "0.3") (Just "@0.3@") (Just "@0@") (Just "'Sfdp', 'Fdp' only"), makeAttr "URL" ["URL", "href"] "ENGC" (EStrng) Nothing (Just "\"\"") (Just "none") Nothing (Just "svg, postscript, map only"), makeAttr "Area" ["area"] "NC" (Dbl) Nothing (Just "1.0") (Just "@1.0@") (Just "@>0@") (Just "'Patchwork' only, requires Graphviz >= 2.30.0"), makeAttr "ArrowHead" ["arrowhead"] "E" (Cust "ArrowType") Nothing (Just "normal") (Just "@'normal'@") Nothing Nothing, makeAttr "ArrowSize" ["arrowsize"] "E" (Dbl) Nothing (Just "1.0") (Just "@1.0@") (Just "@0.0@") Nothing, makeAttr "ArrowTail" ["arrowtail"] "E" (Cust "ArrowType") Nothing (Just "normal") (Just "@'normal'@") Nothing Nothing, makeAttr "Background" ["_background"] "G" (Strng) Nothing (Just "\"\"") (Just "none") Nothing (Just "xdot only"), makeAttr "BoundingBox" ["bb"] "G" (Cust "Rect") Nothing Nothing Nothing Nothing (Just "write only"), makeAttr "BgColor" ["bgcolor"] "GC" (Cust "ColorList") Nothing (Just "[]") (Just "@[]@") Nothing Nothing, makeAttr "Center" ["center"] "G" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing Nothing, makeAttr "ClusterRank" ["clusterrank"] "G" (Cust "ClusterMode") Nothing (Just "Local") (Just "@'Local'@") Nothing (Just "'Dot' only"), makeAttr "Color" ["color"] "ENC" (Cust "ColorList") Nothing (Just "[toWColor Black]") (Just "@['WC' ('X11Color' 'Black') Nothing]@") Nothing Nothing, makeAttr "ColorScheme" ["colorscheme"] "ENCG" (Cust "ColorScheme") Nothing (Just "X11") (Just "@'X11'@") Nothing Nothing, makeAttr "Comment" ["comment"] "ENG" (Strng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing Nothing, makeAttr "Compound" ["compound"] "G" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing (Just "'Dot' only"), makeAttr "Concentrate" ["concentrate"] "G" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing Nothing, makeAttr "Constraint" ["constraint"] "E" (Bl) (Just "True") (Just "True") (Just "@'True'@") Nothing (Just "'Dot' only"), makeAttr "Decorate" ["decorate"] "E" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing Nothing, makeAttr "DefaultDist" ["defaultdist"] "G" (Dbl) Nothing Nothing (Just "@1+(avg. len)*sqrt(abs(V))@ (unable to statically define)") (Just "The value of 'Epsilon'.") (Just "'Neato' only, only if @'Pack' 'DontPack'@"), makeAttr "Dim" ["dim"] "G" (Integ) Nothing (Just "2") (Just "@2@") (Just "@2@") (Just "maximum of @10@; 'Sfdp', 'Fdp', 'Neato' only"), makeAttr "Dimen" ["dimen"] "G" (Integ) Nothing (Just "2") (Just "@2@") (Just "@2@") (Just "maximum of @10@; 'Sfdp', 'Fdp', 'Neato' only"), makeAttr "Dir" ["dir"] "E" (Cust "DirType") Nothing Nothing (Just "@'Forward'@ (directed), @'NoDir'@ (undirected)") Nothing Nothing, makeAttr "DirEdgeConstraints" ["diredgeconstraints"] "G" (Cust "DEConstraints") (Just "EdgeConstraints") (Just "NoConstraints") (Just "@'NoConstraints'@") Nothing (Just "'Neato' only"), makeAttr "Distortion" ["distortion"] "N" (Dbl) Nothing (Just "0.0") (Just "@0.0@") (Just "@-100.0@") Nothing, makeAttr "DPI" ["dpi", "resolution"] "G" (Dbl) Nothing (Just "96.0") (Just "@96.0@, @0.0@") Nothing (Just "svg, bitmap output only; \\\"resolution\\\" is a synonym"), makeAttr "EdgeURL" ["edgeURL", "edgehref"] "E" (EStrng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "svg, map only"), makeAttr "EdgeTarget" ["edgetarget"] "E" (EStrng) Nothing Nothing (Just "none") Nothing (Just "svg, map only"), makeAttr "EdgeTooltip" ["edgetooltip"] "E" (EStrng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "svg, cmap only"), makeAttr "Epsilon" ["epsilon"] "G" (Dbl) Nothing Nothing (Just "@.0001 * # nodes@ (@mode == 'KK'@), @.0001@ (@mode == 'Major'@)") Nothing (Just "'Neato' only"), makeAttr "ESep" ["esep"] "G" (Cust "DPoint") Nothing (Just "(DVal 3)") (Just "@'DVal' 3@") Nothing (Just "not 'Dot'"), makeAttr "FillColor" ["fillcolor"] "NEC" (Cust "ColorList") Nothing (Just "[toWColor Black]") (Just "@['WC' ('X11Color' 'LightGray') Nothing]@ (nodes), @['WC' ('X11Color' 'Black') Nothing]@ (clusters)") Nothing Nothing, makeAttr "FixedSize" ["fixedsize"] "N" (Cust "NodeSize") (Just "SetNodeSize") (Just "GrowAsNeeded") (Just "@'GrowAsNeeded'@") Nothing Nothing, makeAttr "FontColor" ["fontcolor"] "ENGC" (Cust "Color") Nothing (Just "(X11Color Black)") (Just "@'X11Color' 'Black'@") Nothing Nothing, makeAttr "FontName" ["fontname"] "ENGC" (Strng) Nothing (Just "\"Times-Roman\"") (Just "@\\\"Times-Roman\\\"@") Nothing Nothing, makeAttr "FontNames" ["fontnames"] "G" (Cust "SVGFontNames") Nothing (Just "SvgNames") (Just "@'SvgNames'@") Nothing (Just "svg only"), makeAttr "FontPath" ["fontpath"] "G" (Cust "Paths") Nothing Nothing (Just "system dependent") Nothing Nothing, makeAttr "FontSize" ["fontsize"] "ENGC" (Dbl) Nothing (Just "14.0") (Just "@14.0@") (Just "@1.0@") Nothing, makeAttr "ForceLabels" ["forcelabels"] "G" (Bl) (Just "True") (Just "True") (Just "@'True'@") Nothing (Just "only for 'XLabel' attributes, requires Graphviz >= 2.29.0"), makeAttr "GradientAngle" ["gradientangle"] "NCG" (Integ) Nothing (Just "0") (Just "0") Nothing (Just "requires Graphviz >= 2.29.0"), makeAttr "Group" ["group"] "N" (Strng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "'Dot' only"), makeAttr "HeadURL" ["headURL", "headhref"] "E" (EStrng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "svg, map only"), makeAttr "Head_LP" ["head_lp"] "E" (Cust "Point") Nothing Nothing Nothing Nothing (Just "write only, requires Graphviz >= 2.30.0"), makeAttr "HeadClip" ["headclip"] "E" (Bl) (Just "True") (Just "True") (Just "@'True'@") Nothing Nothing, makeAttr "HeadLabel" ["headlabel"] "E" (Cust "Label") Nothing (Just "(StrLabel \"\")") (Just "@'StrLabel' \\\"\\\"@") Nothing Nothing, makeAttr "HeadPort" ["headport"] "E" (Cust "PortPos") Nothing (Just "(CompassPoint CenterPoint)") (Just "@'CompassPoint' 'CenterPoint'@") Nothing Nothing, makeAttr "HeadTarget" ["headtarget"] "E" (EStrng) Nothing (Just "\"\"") (Just "none") Nothing (Just "svg, map only"), makeAttr "HeadTooltip" ["headtooltip"] "E" (EStrng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "svg, cmap only"), makeAttr "Height" ["height"] "N" (Dbl) Nothing (Just "0.5") (Just "@0.5@") (Just "@0.02@") Nothing, makeAttr "ID" ["id"] "GNE" (EStrng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "svg, postscript, map only"), makeAttr "Image" ["image"] "N" (Strng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing Nothing, makeAttr "ImagePath" ["imagepath"] "G" (Cust "Paths") Nothing (Just "(Paths [])") (Just "@'Paths' []@") Nothing (Just "Printing and parsing is OS-specific, requires Graphviz >= 2.29.0"), makeAttr "ImageScale" ["imagescale"] "N" (Cust "ScaleType") (Just "UniformScale") (Just "NoScale") (Just "@'NoScale'@") Nothing Nothing, makeAttr "InputScale" ["inputscale"] "N" (Dbl) Nothing Nothing (Just "none") Nothing (Just "'Fdp', 'Neato' only, a value of @0@ is equivalent to being @72@, requires Graphviz >= 2.36.0"), makeAttr "Label" ["label"] "ENGC" (Cust "Label") Nothing (Just "(StrLabel \"\")") (Just "@'StrLabel' \\\"\\\\N\\\"@ (nodes), @'StrLabel' \\\"\\\"@ (otherwise)") Nothing Nothing, makeAttr "LabelURL" ["labelURL", "labelhref"] "E" (EStrng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "svg, map only"), makeAttr "LabelScheme" ["label_scheme"] "G" (Cust "LabelScheme") Nothing (Just "NotEdgeLabel") (Just "@'NotEdgeLabel'@") Nothing (Just "'Sfdp' only, requires Graphviz >= 2.28.0"), makeAttr "LabelAngle" ["labelangle"] "E" (Dbl) Nothing (Just "(-25.0)") (Just "@-25.0@") (Just "@-180.0@") Nothing, makeAttr "LabelDistance" ["labeldistance"] "E" (Dbl) Nothing (Just "1.0") (Just "@1.0@") (Just "@0.0@") Nothing, makeAttr "LabelFloat" ["labelfloat"] "E" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing Nothing, makeAttr "LabelFontColor" ["labelfontcolor"] "E" (Cust "Color") Nothing (Just "(X11Color Black)") (Just "@'X11Color' 'Black'@") Nothing Nothing, makeAttr "LabelFontName" ["labelfontname"] "E" (Strng) Nothing (Just "\"Times-Roman\"") (Just "@\\\"Times-Roman\\\"@") Nothing Nothing, makeAttr "LabelFontSize" ["labelfontsize"] "E" (Dbl) Nothing (Just "14.0") (Just "@14.0@") (Just "@1.0@") Nothing, makeAttr "LabelJust" ["labeljust"] "GC" (Cust "Justification") Nothing (Just "JCenter") (Just "@'JCenter'@") Nothing Nothing, makeAttr "LabelLoc" ["labelloc"] "GCN" (Cust "VerticalPlacement") Nothing (Just "VTop") (Just "@'VTop'@ (clusters), @'VBottom'@ (root graphs), @'VCenter'@ (nodes)") Nothing Nothing, makeAttr "LabelTarget" ["labeltarget"] "E" (EStrng) Nothing (Just "\"\"") (Just "none") Nothing (Just "svg, map only"), makeAttr "LabelTooltip" ["labeltooltip"] "E" (EStrng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "svg, cmap only"), makeAttr "Landscape" ["landscape"] "G" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing Nothing, makeAttr "Layer" ["layer"] "ENC" (Cust "LayerRange") Nothing (Just "[]") (Just "@[]@") Nothing Nothing, makeAttr "LayerListSep" ["layerlistsep"] "G" (Cust "LayerListSep") Nothing (Just "(LLSep \",\")") (Just "@'LLSep' \\\",\\\"@") Nothing (Just "requires Graphviz >= 2.30.0"), makeAttr "Layers" ["layers"] "G" (Cust "LayerList") Nothing (Just "(LL [])") (Just "@'LL' []@") Nothing Nothing, makeAttr "LayerSelect" ["layerselect"] "G" (Cust "LayerRange") Nothing (Just "[]") (Just "@[]@") Nothing Nothing, makeAttr "LayerSep" ["layersep"] "G" (Cust "LayerSep") Nothing (Just "(LSep \" :\\t\")") (Just "@'LSep' \\\" :\\t\\\"@") Nothing Nothing, makeAttr "Layout" ["layout"] "G" (Cust "GraphvizCommand") Nothing Nothing Nothing Nothing Nothing, makeAttr "Len" ["len"] "E" (Dbl) Nothing Nothing (Just "@1.0@ ('Neato'), @0.3@ ('Fdp')") Nothing (Just "'Fdp', 'Neato' only"), makeAttr "Levels" ["levels"] "G" (Integ) Nothing (Just "maxBound") (Just "@'maxBound'@") (Just "@0@") (Just "'Sfdp' only"), makeAttr "LevelsGap" ["levelsgap"] "G" (Dbl) Nothing (Just "0.0") (Just "@0.0@") Nothing (Just "'Neato' only"), makeAttr "LHead" ["lhead"] "E" (Strng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "'Dot' only"), makeAttr "LHeight" ["LHeight"] "GC" (Dbl) Nothing Nothing Nothing Nothing (Just "write only, requires Graphviz >= 2.28.0"), makeAttr "LPos" ["lp"] "EGC" (Cust "Point") Nothing Nothing Nothing Nothing (Just "write only"), makeAttr "LTail" ["ltail"] "E" (Strng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "'Dot' only"), makeAttr "LWidth" ["lwidth"] "GC" (Dbl) Nothing Nothing Nothing Nothing (Just "write only, requires Graphviz >= 2.28.0"), makeAttr "Margin" ["margin"] "NGC" (Cust "DPoint") Nothing Nothing (Just "device dependent") Nothing Nothing, makeAttr "MaxIter" ["maxiter"] "G" (Integ) Nothing Nothing (Just "@100 * # nodes@ (@mode == 'KK'@), @200@ (@mode == 'Major'@), @600@ ('Fdp')") Nothing (Just "'Fdp', 'Neato' only"), makeAttr "MCLimit" ["mclimit"] "G" (Dbl) Nothing (Just "1.0") (Just "@1.0@") Nothing (Just "'Dot' only"), makeAttr "MinDist" ["mindist"] "G" (Dbl) Nothing (Just "1.0") (Just "@1.0@") (Just "@0.0@") (Just "'Circo' only"), makeAttr "MinLen" ["minlen"] "E" (Integ) Nothing (Just "1") (Just "@1@") (Just "@0@") (Just "'Dot' only"), makeAttr "Mode" ["mode"] "G" (Cust "ModeType") Nothing (Just "Major") (Just "@'Major'@ (actually @'Spring'@ for 'Sfdp', but this isn't used as a default in this library)") Nothing (Just "'Neato', 'Sfdp' only"), makeAttr "Model" ["model"] "G" (Cust "Model") Nothing (Just "ShortPath") (Just "@'ShortPath'@") Nothing (Just "'Neato' only"), makeAttr "Mosek" ["mosek"] "G" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing (Just "'Neato' only; requires the Mosek software"), makeAttr "NodeSep" ["nodesep"] "G" (Dbl) Nothing (Just "0.25") (Just "@0.25@") (Just "@0.02@") Nothing, makeAttr "NoJustify" ["nojustify"] "GCNE" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing Nothing, makeAttr "Normalize" ["normalize"] "G" (Cust "Normalized") (Just "IsNormalized") (Just "NotNormalized") (Just "@'NotNormalized'@") Nothing (Just "not 'Dot'"), makeAttr "NoTranslate" ["notranslate"] "G" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing (Just "'Neato' only, requires Graphviz >= 2.38.0"), makeAttr "Nslimit" ["nslimit"] "G" (Dbl) Nothing Nothing Nothing Nothing (Just "'Dot' only"), makeAttr "Nslimit1" ["nslimit1"] "G" (Dbl) Nothing Nothing Nothing Nothing (Just "'Dot' only"), makeAttr "Ordering" ["ordering"] "GN" (Cust "Order") Nothing Nothing (Just "none") Nothing (Just "'Dot' only"), makeAttr "Orientation" ["orientation"] "N" (Dbl) Nothing (Just "0.0") (Just "@0.0@") (Just "@360.0@") Nothing, makeAttr "OutputOrder" ["outputorder"] "G" (Cust "OutputMode") Nothing (Just "BreadthFirst") (Just "@'BreadthFirst'@") Nothing Nothing, makeAttr "Overlap" ["overlap"] "G" (Cust "Overlap") (Just "KeepOverlaps") (Just "KeepOverlaps") (Just "@'KeepOverlaps'@") Nothing (Just "not 'Dot'"), makeAttr "OverlapScaling" ["overlap_scaling"] "G" (Dbl) Nothing (Just "(-4)") (Just "@-4@") (Just "@-1.0e10@") (Just "'PrismOverlap' only"), makeAttr "OverlapShrink" ["overlap_shrink"] "G" (Bl) (Just "True") (Just "True") (Just "@'True'@") Nothing (Just "'PrismOverlap' only, requires Graphviz >= 2.36.0"), makeAttr "Pack" ["pack"] "G" (Cust "Pack") (Just "DoPack") (Just "DontPack") (Just "@'DontPack'@") Nothing Nothing, makeAttr "PackMode" ["packmode"] "G" (Cust "PackMode") Nothing (Just "PackNode") (Just "@'PackNode'@") Nothing Nothing, makeAttr "Pad" ["pad"] "G" (Cust "DPoint") Nothing (Just "(DVal 0.0555)") (Just "@'DVal' 0.0555@ (4 points)") Nothing Nothing, makeAttr "Page" ["page"] "G" (Cust "Point") Nothing Nothing Nothing Nothing Nothing, makeAttr "PageDir" ["pagedir"] "G" (Cust "PageDir") Nothing (Just "Bl") (Just "@'Bl'@") Nothing Nothing, makeAttr "PenColor" ["pencolor"] "C" (Cust "Color") Nothing (Just "(X11Color Black)") (Just "@'X11Color' 'Black'@") Nothing Nothing, makeAttr "PenWidth" ["penwidth"] "CNE" (Dbl) Nothing (Just "1.0") (Just "@1.0@") (Just "@0.0@") Nothing, makeAttr "Peripheries" ["peripheries"] "NC" (Integ) Nothing (Just "1") (Just "shape default (nodes), @1@ (clusters)") (Just "0") Nothing, makeAttr "Pin" ["pin"] "N" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing (Just "'Fdp', 'Neato' only"), makeAttr "Pos" ["pos"] "EN" (Cust "Pos") Nothing Nothing Nothing Nothing Nothing, makeAttr "QuadTree" ["quadtree"] "G" (Cust "QuadType") (Just "NormalQT") (Just "NormalQT") (Just "@'NormalQT'@") Nothing (Just "'Sfdp' only"), makeAttr "Quantum" ["quantum"] "G" (Dbl) Nothing (Just "0") (Just "@0.0@") (Just "@0.0@") Nothing, makeAttr "Rank" ["rank"] "S" (Cust "RankType") Nothing Nothing Nothing Nothing (Just "'Dot' only"), makeAttr "RankDir" ["rankdir"] "G" (Cust "RankDir") Nothing (Just "FromTop") (Just "@'FromTop'@") Nothing (Just "'Dot' only"), makeAttr "RankSep" ["ranksep"] "G" (Cust "[Double]") Nothing Nothing (Just "@[0.5]@ ('Dot'), @[1.0]@ ('Twopi')") (Just "@[0.02]@") (Just "'Twopi', 'Dot' only"), makeAttr "Ratio" ["ratio"] "G" (Cust "Ratios") Nothing Nothing Nothing Nothing Nothing, makeAttr "Rects" ["rects"] "N" (Cust "[Rect]") Nothing Nothing Nothing Nothing (Just "write only"), makeAttr "Regular" ["regular"] "N" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing Nothing, makeAttr "ReMinCross" ["remincross"] "G" (Bl) (Just "True") (Just "False") (Just "@'False'@") Nothing (Just "'Dot' only"), makeAttr "RepulsiveForce" ["repulsiveforce"] "G" (Dbl) Nothing (Just "1.0") (Just "@1.0@") (Just "@0.0@") (Just "'Sfdp' only"), makeAttr "Root" ["root"] "GN" (Cust "Root") (Just "IsCentral") (Just "(NodeName \"\")") (Just "@'NodeName' \\\"\\\"@ (graphs), @'NotCentral'@ (nodes)") Nothing (Just "'Circo', 'Twopi' only"), makeAttr "Rotate" ["rotate"] "G" (Integ) Nothing (Just "0") (Just "@0@") Nothing Nothing, makeAttr "Rotation" ["rotation"] "G" (Dbl) Nothing (Just "0") (Just "@0@") Nothing (Just "'Sfdp' only, requires Graphviz >= 2.28.0"), makeAttr "SameHead" ["samehead"] "E" (Strng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "'Dot' only"), makeAttr "SameTail" ["sametail"] "E" (Strng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "'Dot' only"), makeAttr "SamplePoints" ["samplepoints"] "N" (Integ) Nothing Nothing (Just "@8@ (output), @20@ (overlap and image maps)") Nothing Nothing, makeAttr "Scale" ["scale"] "G" (Cust "DPoint") Nothing Nothing Nothing Nothing (Just "Not 'Dot', requires Graphviz >= 2.28.0 (>= 2.38.0 for anything except 'TwoPi')"), makeAttr "SearchSize" ["searchsize"] "G" (Integ) Nothing (Just "30") (Just "@30@") Nothing (Just "'Dot' only"), makeAttr "Sep" ["sep"] "G" (Cust "DPoint") Nothing (Just "(DVal 4)") (Just "@'DVal' 4@") Nothing (Just "not 'Dot'"), makeAttr "Shape" ["shape"] "N" (Cust "Shape") Nothing (Just "Ellipse") (Just "@'Ellipse'@") Nothing Nothing, makeAttr "ShowBoxes" ["showboxes"] "ENG" (Integ) Nothing (Just "0") (Just "@0@") (Just "@0@") (Just "'Dot' only; used for debugging by printing PostScript guide boxes"), makeAttr "Sides" ["sides"] "N" (Integ) Nothing (Just "4") (Just "@4@") (Just "@0@") Nothing, makeAttr "Size" ["size"] "G" (Cust "GraphSize") Nothing Nothing Nothing Nothing Nothing, makeAttr "Skew" ["skew"] "N" (Dbl) Nothing (Just "0.0") (Just "@0.0@") (Just "@-100.0@") Nothing, makeAttr "Smoothing" ["smoothing"] "G" (Cust "SmoothType") Nothing (Just "NoSmooth") (Just "@'NoSmooth'@") Nothing (Just "'Sfdp' only"), makeAttr "SortV" ["sortv"] "GCN" (Cust "Word16") Nothing (Just "0") (Just "@0@") (Just "@0@") Nothing, makeAttr "Splines" ["splines"] "G" (Cust "EdgeType") (Just "SplineEdges") Nothing (Just "@'SplineEdges'@ ('Dot'), @'LineEdges'@ (other)") Nothing Nothing, makeAttr "Start" ["start"] "G" (Cust "StartType") Nothing Nothing (Just "@'StartStyleSeed' 'RandomStyle' seed@ for some unknown fixed seed.") Nothing (Just "'Fdp', 'Neato' only"), makeAttr "Style" ["style"] "ENCG" (Cust "[StyleItem]") Nothing Nothing Nothing Nothing Nothing, makeAttr "StyleSheet" ["stylesheet"] "G" (Strng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "svg only"), makeAttr "TailURL" ["tailURL", "tailhref"] "E" (EStrng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "svg, map only"), makeAttr "Tail_LP" ["tail_lp"] "E" (Cust "Point") Nothing Nothing Nothing Nothing (Just "write only, requires Graphviz >= 2.30.0"), makeAttr "TailClip" ["tailclip"] "E" (Bl) (Just "True") (Just "True") (Just "@'True'@") Nothing Nothing, makeAttr "TailLabel" ["taillabel"] "E" (Cust "Label") Nothing (Just "(StrLabel \"\")") (Just "@'StrLabel' \\\"\\\"@") Nothing Nothing, makeAttr "TailPort" ["tailport"] "E" (Cust "PortPos") Nothing (Just "(CompassPoint CenterPoint)") (Just "@'CompassPoint' 'CenterPoint'@") Nothing Nothing, makeAttr "TailTarget" ["tailtarget"] "E" (EStrng) Nothing (Just "\"\"") (Just "none") Nothing (Just "svg, map only"), makeAttr "TailTooltip" ["tailtooltip"] "E" (EStrng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "svg, cmap only"), makeAttr "Target" ["target"] "ENGC" (EStrng) Nothing (Just "\"\"") (Just "none") Nothing (Just "svg, map only"), makeAttr "Tooltip" ["tooltip"] "NEC" (EStrng) Nothing (Just "\"\"") (Just "@\\\"\\\"@") Nothing (Just "svg, cmap only"), makeAttr "TrueColor" ["truecolor"] "G" (Bl) (Just "True") Nothing Nothing Nothing (Just "bitmap output only"), makeAttr "Vertices" ["vertices"] "N" (Cust "[Point]") Nothing Nothing Nothing Nothing (Just "write only"), makeAttr "ViewPort" ["viewport"] "G" (Cust "ViewPort") Nothing Nothing (Just "none") Nothing Nothing, makeAttr "VoroMargin" ["voro_margin"] "G" (Dbl) Nothing (Just "0.05") (Just "@0.05@") (Just "@0.0@") (Just "not 'Dot'"), makeAttr "Weight" ["weight"] "E" (Cust "Number") Nothing (Just "(Int 1)") (Just "@'Int' 1@") (Just "@'Int' 0@ ('Dot'), @'Int' 1@ ('Neato','Fdp','Sfdp')") (Just "as of Graphviz 2.30: weights for dot need to be 'Int's"), makeAttr "Width" ["width"] "N" (Dbl) Nothing (Just "0.75") (Just "@0.75@") (Just "@0.01@") Nothing, makeAttr "XDotVersion" ["xdotversion"] "G" (Cust "Version") Nothing Nothing Nothing Nothing (Just "xdot only, requires Graphviz >= 2.34.0, equivalent to specifying version of xdot to be used"), makeAttr "XLabel" ["xlabel"] "EN" (Cust "Label") Nothing (Just "(StrLabel \"\")") (Just "@'StrLabel' \\\"\\\"@") Nothing (Just "requires Graphviz >= 2.29.0"), makeAttr "XLP" ["xlp"] "EN" (Cust "Point") Nothing Nothing Nothing Nothing (Just "write only, requires Graphviz >= 2.29.0") -- END RECEIVE ORGTBL Attributes ] {- When using Emacs with org-mode available, hitting ` C-c C-c ' inside the table below should update the actual Haskell code above. This way, you can more easily edit/update the appropriate values. * Values in "Allowed names" should be space-separated (and are converted into a list of Strings). * Used by should consist of a sub-set of `ENGCS'. * The entries in "Type" should be a valid Haskell value of type 'VType' (parens are added). * An empty cell in the last five columns translates to a `Nothing' value; anything else is wrapped in quotes and then has Just applied to it. As such, you still need to escape quotes. * Any entries in 'Parsing default' or "Default value" should be a valid Haskell value (add parens if needed) with the exception that double-quotes should be escaped. * @C-c `@ can be used to edit a field that has been narrowed. #+ORGTBL: SEND Attributes orgtbl-to-generic :skip 2 :splice t :hline nil :no-escape t :lstart " makeAttr " :lend "," :llend "" :sep " " :fmt (1 cell-quote 2 cell-to-list 3 cell-quote 4 cell-parens 5 cell-to-maybe 6 cell-to-maybe 7 cell-to-maybe 8 cell-to-maybe 9 cell-to-maybe) | Constructor | Allowed names | Used By | Type | Parse def | Default value | Default for Documentation | Minimum | Comment notes | |-----------------+-----------------+---------+-----------------+------------+-----------------+----------------------+------------+----------------------| | <15> | <15> | | <15> | <10> | <15> | <20> | <10> | <20> | | Damping | Damping | G | Dbl | | 0.99 | @0.99@ | @0.0@ | 'Neato' only | | K | K | GC | Dbl | | 0.3 | @0.3@ | @0@ | 'Sfdp', 'Fdp' only | | URL | URL href | ENGC | EStrng | | \"\" | none | | svg, postscript, map only | | Area | area | NC | Dbl | | 1.0 | @1.0@ | @>0@ | 'Patchwork' only, requires Graphviz >= 2.30.0 | | ArrowHead | arrowhead | E | Cust "ArrowType" | | normal | @'normal'@ | | | | ArrowSize | arrowsize | E | Dbl | | 1.0 | @1.0@ | @0.0@ | | | ArrowTail | arrowtail | E | Cust "ArrowType" | | normal | @'normal'@ | | | | Background | _background | G | Strng | | \"\" | none | | xdot only | | BoundingBox | bb | G | Cust "Rect" | | | | | write only | | BgColor | bgcolor | GC | Cust "ColorList" | | [] | @[]@ | | | | Center | center | G | Bl | True | False | @'False'@ | | | | ClusterRank | clusterrank | G | Cust "ClusterMode" | | Local | @'Local'@ | | 'Dot' only | | Color | color | ENC | Cust "ColorList" | | [toWColor Black] | @['WC' ('X11Color' 'Black') Nothing]@ | | | | ColorScheme | colorscheme | ENCG | Cust "ColorScheme" | | X11 | @'X11'@ | | | | Comment | comment | ENG | Strng | | \"\" | @\\\"\\\"@ | | | | Compound | compound | G | Bl | True | False | @'False'@ | | 'Dot' only | | Concentrate | concentrate | G | Bl | True | False | @'False'@ | | | | Constraint | constraint | E | Bl | True | True | @'True'@ | | 'Dot' only | | Decorate | decorate | E | Bl | True | False | @'False'@ | | | | DefaultDist | defaultdist | G | Dbl | | | @1+(avg. len)*sqrt(abs(V))@ (unable to statically define) | The value of 'Epsilon'. | 'Neato' only, only if @'Pack' 'DontPack'@ | | Dim | dim | G | Integ | | 2 | @2@ | @2@ | maximum of @10@; 'Sfdp', 'Fdp', 'Neato' only | | Dimen | dimen | G | Integ | | 2 | @2@ | @2@ | maximum of @10@; 'Sfdp', 'Fdp', 'Neato' only | | Dir | dir | E | Cust "DirType" | | | @'Forward'@ (directed), @'NoDir'@ (undirected) | | | | DirEdgeConstraints | diredgeconstraints | G | Cust "DEConstraints" | EdgeConstraints | NoConstraints | @'NoConstraints'@ | | 'Neato' only | | Distortion | distortion | N | Dbl | | 0.0 | @0.0@ | @-100.0@ | | | DPI | dpi resolution | G | Dbl | | 96.0 | @96.0@, @0.0@ | | svg, bitmap output only; \\\"resolution\\\" is a synonym | | EdgeURL | edgeURL edgehref | E | EStrng | | \"\" | @\\\"\\\"@ | | svg, map only | | EdgeTarget | edgetarget | E | EStrng | | | none | | svg, map only | | EdgeTooltip | edgetooltip | E | EStrng | | \"\" | @\\\"\\\"@ | | svg, cmap only | | Epsilon | epsilon | G | Dbl | | | @.0001 * # nodes@ (@mode == 'KK'@), @.0001@ (@mode == 'Major'@) | | 'Neato' only | | ESep | esep | G | Cust "DPoint" | | (DVal 3) | @'DVal' 3@ | | not 'Dot' | | FillColor | fillcolor | NEC | Cust "ColorList" | | [toWColor Black] | @['WC' ('X11Color' 'LightGray') Nothing]@ (nodes), @['WC' ('X11Color' 'Black') Nothing]@ (clusters) | | | | FixedSize | fixedsize | N | Cust "NodeSize" | SetNodeSize | GrowAsNeeded | @'GrowAsNeeded'@ | | | | FontColor | fontcolor | ENGC | Cust "Color" | | (X11Color Black) | @'X11Color' 'Black'@ | | | | FontName | fontname | ENGC | Strng | | \"Times-Roman\" | @\\\"Times-Roman\\\"@ | | | | FontNames | fontnames | G | Cust "SVGFontNames" | | SvgNames | @'SvgNames'@ | | svg only | | FontPath | fontpath | G | Cust "Paths" | | | system dependent | | | | FontSize | fontsize | ENGC | Dbl | | 14.0 | @14.0@ | @1.0@ | | | ForceLabels | forcelabels | G | Bl | True | True | @'True'@ | | only for 'XLabel' attributes, requires Graphviz >= 2.29.0 | | GradientAngle | gradientangle | NCG | Integ | | 0 | 0 | | requires Graphviz >= 2.29.0 | | Group | group | N | Strng | | \"\" | @\\\"\\\"@ | | 'Dot' only | | HeadURL | headURL headhref | E | EStrng | | \"\" | @\\\"\\\"@ | | svg, map only | | Head_LP | head_lp | E | Cust "Point" | | | | | write only, requires Graphviz >= 2.30.0 | | HeadClip | headclip | E | Bl | True | True | @'True'@ | | | | HeadLabel | headlabel | E | Cust "Label" | | (StrLabel \"\") | @'StrLabel' \\\"\\\"@ | | | | HeadPort | headport | E | Cust "PortPos" | | (CompassPoint CenterPoint) | @'CompassPoint' 'CenterPoint'@ | | | | HeadTarget | headtarget | E | EStrng | | \"\" | none | | svg, map only | | HeadTooltip | headtooltip | E | EStrng | | \"\" | @\\\"\\\"@ | | svg, cmap only | | Height | height | N | Dbl | | 0.5 | @0.5@ | @0.02@ | | | ID | id | GNE | EStrng | | \"\" | @\\\"\\\"@ | | svg, postscript, map only | | Image | image | N | Strng | | \"\" | @\\\"\\\"@ | | | | ImagePath | imagepath | G | Cust "Paths" | | (Paths []) | @'Paths' []@ | | Printing and parsing is OS-specific, requires Graphviz >= 2.29.0 | | ImageScale | imagescale | N | Cust "ScaleType" | UniformScale | NoScale | @'NoScale'@ | | | | InputScale | inputscale | N | Dbl | | | none | | 'Fdp', 'Neato' only, a value of @0@ is equivalent to being @72@, requires Graphviz >= 2.36.0 | | Label | label | ENGC | Cust "Label" | | (StrLabel \"\") | @'StrLabel' \\\"\\\\N\\\"@ (nodes), @'StrLabel' \\\"\\\"@ (otherwise) | | | | LabelURL | labelURL labelhref | E | EStrng | | \"\" | @\\\"\\\"@ | | svg, map only | | LabelScheme | label_scheme | G | Cust "LabelScheme" | | NotEdgeLabel | @'NotEdgeLabel'@ | | 'Sfdp' only, requires Graphviz >= 2.28.0 | | LabelAngle | labelangle | E | Dbl | | (-25.0) | @-25.0@ | @-180.0@ | | | LabelDistance | labeldistance | E | Dbl | | 1.0 | @1.0@ | @0.0@ | | | LabelFloat | labelfloat | E | Bl | True | False | @'False'@ | | | | LabelFontColor | labelfontcolor | E | Cust "Color" | | (X11Color Black) | @'X11Color' 'Black'@ | | | | LabelFontName | labelfontname | E | Strng | | \"Times-Roman\" | @\\\"Times-Roman\\\"@ | | | | LabelFontSize | labelfontsize | E | Dbl | | 14.0 | @14.0@ | @1.0@ | | | LabelJust | labeljust | GC | Cust "Justification" | | JCenter | @'JCenter'@ | | | | LabelLoc | labelloc | GCN | Cust "VerticalPlacement" | | VTop | @'VTop'@ (clusters), @'VBottom'@ (root graphs), @'VCenter'@ (nodes) | | | | LabelTarget | labeltarget | E | EStrng | | \"\" | none | | svg, map only | | LabelTooltip | labeltooltip | E | EStrng | | \"\" | @\\\"\\\"@ | | svg, cmap only | | Landscape | landscape | G | Bl | True | False | @'False'@ | | | | Layer | layer | ENC | Cust "LayerRange" | | [] | @[]@ | | | | LayerListSep | layerlistsep | G | Cust "LayerListSep" | | (LLSep \",\") | @'LLSep' \\\",\\\"@ | | requires Graphviz >= 2.30.0 | | Layers | layers | G | Cust "LayerList" | | (LL []) | @'LL' []@ | | | | LayerSelect | layerselect | G | Cust "LayerRange" | | [] | @[]@ | | | | LayerSep | layersep | G | Cust "LayerSep" | | (LSep \" :\\t\") | @'LSep' \\\" :\\t\\\"@ | | | | Layout | layout | G | Cust "GraphvizCommand" | | | | | | | Len | len | E | Dbl | | | @1.0@ ('Neato'), @0.3@ ('Fdp') | | 'Fdp', 'Neato' only | | Levels | levels | G | Integ | | maxBound | @'maxBound'@ | @0@ | 'Sfdp' only | | LevelsGap | levelsgap | G | Dbl | | 0.0 | @0.0@ | | 'Neato' only | | LHead | lhead | E | Strng | | \"\" | @\\\"\\\"@ | | 'Dot' only | | LHeight | LHeight | GC | Dbl | | | | | write only, requires Graphviz >= 2.28.0 | | LPos | lp | EGC | Cust "Point" | | | | | write only | | LTail | ltail | E | Strng | | \"\" | @\\\"\\\"@ | | 'Dot' only | | LWidth | lwidth | GC | Dbl | | | | | write only, requires Graphviz >= 2.28.0 | | Margin | margin | NGC | Cust "DPoint" | | | device dependent | | | | MaxIter | maxiter | G | Integ | | | @100 * # nodes@ (@mode == 'KK'@), @200@ (@mode == 'Major'@), @600@ ('Fdp') | | 'Fdp', 'Neato' only | | MCLimit | mclimit | G | Dbl | | 1.0 | @1.0@ | | 'Dot' only | | MinDist | mindist | G | Dbl | | 1.0 | @1.0@ | @0.0@ | 'Circo' only | | MinLen | minlen | E | Integ | | 1 | @1@ | @0@ | 'Dot' only | | Mode | mode | G | Cust "ModeType" | | Major | @'Major'@ (actually @'Spring'@ for 'Sfdp', but this isn't used as a default in this library) | | 'Neato', 'Sfdp' only | | Model | model | G | Cust "Model" | | ShortPath | @'ShortPath'@ | | 'Neato' only | | Mosek | mosek | G | Bl | True | False | @'False'@ | | 'Neato' only; requires the Mosek software | | NodeSep | nodesep | G | Dbl | | 0.25 | @0.25@ | @0.02@ | | | NoJustify | nojustify | GCNE | Bl | True | False | @'False'@ | | | | Normalize | normalize | G | Cust "Normalized" | IsNormalized | NotNormalized | @'NotNormalized'@ | | not 'Dot' | | NoTranslate | notranslate | G | Bl | True | False | @'False'@ | | 'Neato' only, requires Graphviz >= 2.38.0 | | Nslimit | nslimit | G | Dbl | | | | | 'Dot' only | | Nslimit1 | nslimit1 | G | Dbl | | | | | 'Dot' only | | Ordering | ordering | GN | Cust "Order" | | | none | | 'Dot' only | | Orientation | orientation | N | Dbl | | 0.0 | @0.0@ | @360.0@ | | | OutputOrder | outputorder | G | Cust "OutputMode" | | BreadthFirst | @'BreadthFirst'@ | | | | Overlap | overlap | G | Cust "Overlap" | KeepOverlaps | KeepOverlaps | @'KeepOverlaps'@ | | not 'Dot' | | OverlapScaling | overlap_scaling | G | Dbl | | (-4) | @-4@ | @-1.0e10@ | 'PrismOverlap' only | | OverlapShrink | overlap_shrink | G | Bl | True | True | @'True'@ | | 'PrismOverlap' only, requires Graphviz >= 2.36.0 | | Pack | pack | G | Cust "Pack" | DoPack | DontPack | @'DontPack'@ | | | | PackMode | packmode | G | Cust "PackMode" | | PackNode | @'PackNode'@ | | | | Pad | pad | G | Cust "DPoint" | | (DVal 0.0555) | @'DVal' 0.0555@ (4 points) | | | | Page | page | G | Cust "Point" | | | | | | | PageDir | pagedir | G | Cust "PageDir" | | Bl | @'Bl'@ | | | | PenColor | pencolor | C | Cust "Color" | | (X11Color Black) | @'X11Color' 'Black'@ | | | | PenWidth | penwidth | CNE | Dbl | | 1.0 | @1.0@ | @0.0@ | | | Peripheries | peripheries | NC | Integ | | 1 | shape default (nodes), @1@ (clusters) | 0 | | | Pin | pin | N | Bl | True | False | @'False'@ | | 'Fdp', 'Neato' only | | Pos | pos | EN | Cust "Pos" | | | | | | | QuadTree | quadtree | G | Cust "QuadType" | NormalQT | NormalQT | @'NormalQT'@ | | 'Sfdp' only | | Quantum | quantum | G | Dbl | | 0 | @0.0@ | @0.0@ | | | Rank | rank | S | Cust "RankType" | | | | | 'Dot' only | | RankDir | rankdir | G | Cust "RankDir" | | FromTop | @'FromTop'@ | | 'Dot' only | | RankSep | ranksep | G | Cust "[Double]" | | | @[0.5]@ ('Dot'), @[1.0]@ ('Twopi') | @[0.02]@ | 'Twopi', 'Dot' only | | Ratio | ratio | G | Cust "Ratios" | | | | | | | Rects | rects | N | Cust "[Rect]" | | | | | write only | | Regular | regular | N | Bl | True | False | @'False'@ | | | | ReMinCross | remincross | G | Bl | True | False | @'False'@ | | 'Dot' only | | RepulsiveForce | repulsiveforce | G | Dbl | | 1.0 | @1.0@ | @0.0@ | 'Sfdp' only | | Root | root | GN | Cust "Root" | IsCentral | (NodeName \"\") | @'NodeName' \\\"\\\"@ (graphs), @'NotCentral'@ (nodes) | | 'Circo', 'Twopi' only | | Rotate | rotate | G | Integ | | 0 | @0@ | | | | Rotation | rotation | G | Dbl | | 0 | @0@ | | 'Sfdp' only, requires Graphviz >= 2.28.0 | | SameHead | samehead | E | Strng | | \"\" | @\\\"\\\"@ | | 'Dot' only | | SameTail | sametail | E | Strng | | \"\" | @\\\"\\\"@ | | 'Dot' only | | SamplePoints | samplepoints | N | Integ | | | @8@ (output), @20@ (overlap and image maps) | | | | Scale | scale | G | Cust "DPoint" | | | | | Not 'Dot', requires Graphviz >= 2.28.0 (>= 2.38.0 for anything except 'TwoPi') | | SearchSize | searchsize | G | Integ | | 30 | @30@ | | 'Dot' only | | Sep | sep | G | Cust "DPoint" | | (DVal 4) | @'DVal' 4@ | | not 'Dot' | | Shape | shape | N | Cust "Shape" | | Ellipse | @'Ellipse'@ | | | | ShowBoxes | showboxes | ENG | Integ | | 0 | @0@ | @0@ | 'Dot' only; used for debugging by printing PostScript guide boxes | | Sides | sides | N | Integ | | 4 | @4@ | @0@ | | | Size | size | G | Cust "GraphSize" | | | | | | | Skew | skew | N | Dbl | | 0.0 | @0.0@ | @-100.0@ | | | Smoothing | smoothing | G | Cust "SmoothType" | | NoSmooth | @'NoSmooth'@ | | 'Sfdp' only | | SortV | sortv | GCN | Cust "Word16" | | 0 | @0@ | @0@ | | | Splines | splines | G | Cust "EdgeType" | SplineEdges | | @'SplineEdges'@ ('Dot'), @'LineEdges'@ (other) | | | | Start | start | G | Cust "StartType" | | | @'StartStyleSeed' 'RandomStyle' seed@ for some unknown fixed seed. | | 'Fdp', 'Neato' only | | Style | style | ENCG | Cust "[StyleItem]" | | | | | | | StyleSheet | stylesheet | G | Strng | | \"\" | @\\\"\\\"@ | | svg only | | TailURL | tailURL tailhref | E | EStrng | | \"\" | @\\\"\\\"@ | | svg, map only | | Tail_LP | tail_lp | E | Cust "Point" | | | | | write only, requires Graphviz >= 2.30.0 | | TailClip | tailclip | E | Bl | True | True | @'True'@ | | | | TailLabel | taillabel | E | Cust "Label" | | (StrLabel \"\") | @'StrLabel' \\\"\\\"@ | | | | TailPort | tailport | E | Cust "PortPos" | | (CompassPoint CenterPoint) | @'CompassPoint' 'CenterPoint'@ | | | | TailTarget | tailtarget | E | EStrng | | \"\" | none | | svg, map only | | TailTooltip | tailtooltip | E | EStrng | | \"\" | @\\\"\\\"@ | | svg, cmap only | | Target | target | ENGC | EStrng | | \"\" | none | | svg, map only | | Tooltip | tooltip | NEC | EStrng | | \"\" | @\\\"\\\"@ | | svg, cmap only | | TrueColor | truecolor | G | Bl | True | | | | bitmap output only | | Vertices | vertices | N | Cust "[Point]" | | | | | write only | | ViewPort | viewport | G | Cust "ViewPort" | | | none | | | | VoroMargin | voro_margin | G | Dbl | | 0.05 | @0.05@ | @0.0@ | not 'Dot' | | Weight | weight | E | Cust "Number" | | (Int 1) | @'Int' 1@ | @'Int' 0@ ('Dot'), @'Int' 1@ ('Neato','Fdp','Sfdp') | as of Graphviz 2.30: weights for dot need to be 'Int's | | Width | width | N | Dbl | | 0.75 | @0.75@ | @0.01@ | | | XDotVersion | xdotversion | G | Cust "Version" | | | | | xdot only, requires Graphviz >= 2.34.0, equivalent to specifying version of xdot to be used | | XLabel | xlabel | EN | Cust "Label" | | (StrLabel \"\") | @'StrLabel' \\\"\\\"@ | | requires Graphviz >= 2.29.0 | | XLP | xlp | EN | Cust "Point" | | | | | write only, requires Graphviz >= 2.29.0 | -} unknownAttr :: Doc unknownAttr = text "UnknownAttribute" -- For testing purposes attrs :: [Attribute] attrs = take 10 $ drop 5 attributes -- For testing purposes attrs' :: Atts attrs' = AS (text "Attribute") attrs bool :: a -> a -> Bool -> a bool f t b = if b then t else f dollar :: Doc dollar = char '$' -- Local Variables: -- eval: (turn-on-orgtbl) -- eval: (defun cell-quote (s) (concat "\"" s "\"")) -- eval: (defun cell-parens (s) (concat "(" s ")")) -- eval: (defun cell-to-maybe (s) (if (string= "" s) "Nothing" (cell-parens (concat "Just " (cell-quote s))))) -- eval: (defun cell-to-list (s) (concat "[" (mapconcat 'cell-quote (split-string s) ", ") "]")) -- END: graphviz-2999.20.2.0/LICENSE.md0000644000000000000000000001013614536315671013646 0ustar0000000000000000 Licensing Information ===================== The overall graphviz library is covered by a [3-Clause BSD License]. However, the _ColorBrewer_ colours are licensed under their own license. [3-Clause BSD License]: http://www.opensource.org/licenses/bsd-license.php License for graphviz -------------------- Copyright (c) 2008, Matthew Sackman Copyright (c) 2008 - 2010, [Ivan Lazar Miljenovic](mailto:Ivan.Miljenovic+graphviz@gmail.com) All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * The names of the contributors to this software may not be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. The ColorBrewer license ----------------------- > The _ColorBrewer_ colours and colour schemes found in > `Data.GraphViz.Attributes.Colors` are covered by the following > license. This text is not part of the license. Apache-Style Software License for ColorBrewer software and ColorBrewer Color Schemes, Version 1.1 Copyright (c) 2002 Cynthia Brewer, Mark Harrower, and The Pennsylvania State University. All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: 1. Redistributions as source code must retain the above copyright notice, this list of conditions and the following disclaimer. 2. The end-user documentation included with the redistribution, if any, must include the following acknowledgment: This product includes color specifications and designs developed by Cynthia Brewer (http://colorbrewer.org/). Alternately, this acknowledgment may appear in the software itself, if and wherever such third-party acknowledgments normally appear. 3. The name "ColorBrewer" must not be used to endorse or promote products derived from this software without prior written permission. For written permission, please contact Cynthia Brewer at cbrewer@psu.edu. 4. Products derived from this software may not be called "ColorBrewer", nor may "ColorBrewer" appear in their name, without prior written permission of Cynthia Brewer. THIS SOFTWARE IS PROVIDED "AS IS" AND ANY EXPRESSED OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL CYNTHIA BREWER, MARK HARROWER, OR THE PENNSYLVANIA STATE UNIVERSITY BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. graphviz-2999.20.2.0/graphviz.cabal0000644000000000000000000001611414536315671015062 0ustar0000000000000000Name: graphviz Version: 2999.20.2.0 Stability: Beta Synopsis: Bindings to Graphviz for graph visualisation. Description: { This library provides bindings for the Dot language used by the Graphviz () suite of programs for visualising graphs, as well as functions to call those programs. . Main features of the graphviz library include: . * Almost complete coverage of all Graphviz attributes and syntax. . * Support for specifying clusters. . * The ability to use a custom node type. . * Functions for running a Graphviz layout tool with all specified output types. . * The ability to not only generate but also parse Dot code with two options: strict and liberal (in terms of ordering of statements). . * Functions to convert FGL graphs and other graph-like data structures to Dot code - including support to group them into clusters - with a high degree of customisation by specifying which attributes to use and limited support for the inverse operation. . * Round-trip support for passing an FGL graph through Graphviz to augment node and edge labels with positional information, etc. } Homepage: https://gitlab.com/daniel-casanueva/haskell/graphviz Category: Graphs, Graphics License: BSD3 License-File: LICENSE.md Copyright: Matthew Sackman, Ivan Lazar Miljenovic Author: Matthew Sackman, Ivan Lazar Miljenovic Maintainer: Daniel Casanueva (daniel.casanueva `at` proton.me) Build-Type: Simple Cabal-Version: 1.14 Extra-Source-Files: TODO.md Changelog.md README.md FAQ.md utils/AttributeGenerator.hs Flag test-parsing Description: Build a utility to test parsing of available Dot code. Default: False Library { Default-Language: Haskell2010 Build-Depends: base >=4.5.0.0 && <5, containers, process, directory, temporary >=1.1 && <1.4, fgl >= 5.4 && < 5.9, filepath, polyparse >=1.9 && <1.14, bytestring >= 0.9, colour == 2.3.*, mtl == 2.*, text, wl-pprint-text == 1.2.*, dlist >= 0.5 && < 1.1 Exposed-Modules: Data.GraphViz Data.GraphViz.Types Data.GraphViz.Types.Canonical Data.GraphViz.Types.Generalised Data.GraphViz.Types.Graph Data.GraphViz.Types.Monadic Data.GraphViz.Parsing Data.GraphViz.Printing Data.GraphViz.Commands Data.GraphViz.Commands.IO Data.GraphViz.Attributes Data.GraphViz.Attributes.Complete Data.GraphViz.Attributes.Colors Data.GraphViz.Attributes.Colors.X11 Data.GraphViz.Attributes.Colors.Brewer Data.GraphViz.Attributes.Colors.SVG Data.GraphViz.Attributes.HTML Data.GraphViz.PreProcessing Data.GraphViz.Exception Data.GraphViz.Algorithms Data.GraphViz.Attributes.Internal Data.GraphViz.Internal.Util Data.GraphViz.Internal.State Data.GraphViz.Types.Internal.Common Other-Modules: Data.GraphViz.Algorithms.Clustering Data.GraphViz.Attributes.Arrows Data.GraphViz.Attributes.ColorScheme Data.GraphViz.Attributes.Same Data.GraphViz.Attributes.Values Data.GraphViz.Commands.Available Data.GraphViz.Types.State Ghc-Options: -Wall } Test-Suite graphviz-testsuite { Default-Language: Haskell2010 Type: exitcode-stdio-1.0 -- Versions controlled by library section Build-Depends: base, graphviz, containers, fgl >= 5.5.0.0, fgl-arbitrary == 0.2.*, filepath, hspec >= 2.1 && < 3, text, QuickCheck >= 2.3 && < 2.15 Build-Tool-Depends: hspec-discover:hspec-discover == 2.* hs-Source-Dirs: tests Main-Is: Main.hs Other-Modules: Data.GraphViz.Testing.Instances Data.GraphViz.Testing.Properties Data.GraphViz.Testing.Instances.Helpers Data.GraphViz.Testing.Instances.Attributes Data.GraphViz.Testing.Instances.Common Data.GraphViz.Testing.Instances.Canonical Data.GraphViz.Testing.Instances.Generalised Data.GraphViz.Testing.Instances.Graph Data.GraphViz.Testing.Proxy Data.GraphVizSpec Data.GraphViz.AlgorithmsSpec Data.GraphViz.Attributes.CompleteSpec Data.GraphViz.Attributes.HTMLSpec Data.GraphViz.PreProcessingSpec Data.GraphViz.Types.CanonicalSpec Data.GraphViz.Types.GeneralisedSpec Data.GraphViz.Types.GraphSpec Spec if True Ghc-Options: -Wall if impl(ghc >= 6.12.1) Ghc-Options: -fno-warn-unused-do-bind GHC-Prof-Options: -rtsopts } Benchmark graphviz-printparse { Default-Language: Haskell2010 Type: exitcode-stdio-1.0 Build-Depends: base, deepseq, text, graphviz, criterion >= 0.5 && < 1.7 hs-Source-Dirs: utils Main-Is: Benchmark.hs Ghc-Options: -Wall GHC-Prof-Options: -rtsopts } Executable graphviz-testparsing { Default-Language: Haskell2010 if flag(test-parsing) Buildable: True else Buildable: False hs-Source-Dirs: utils Main-Is: TestParsing.hs Build-Depends: base, graphviz, bytestring, directory, filepath, text Ghc-Options: -Wall GHC-Prof-Options: -rtsopts }