{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module DotParse.Examples.AST where
import Algebra.Graph.Labelled qualified as L
import Data.ByteString (ByteString)
import Data.ByteString.Char8 qualified as B
import Data.List qualified as List
import Data.List.NonEmpty hiding (filter, head, length, map, zip, zipWith, (!!))
import Data.Map.Strict qualified as Map
import Data.Maybe
import Data.Monoid
import Data.String.Interpolate
import Data.These
import DotParse.Types
import GHC.Generics
import Optics.Core
import Prelude hiding (replicate)
data SubComponents = SubComponents
{ SubComponents -> ByteString
classComponent :: ByteString,
SubComponents -> [ByteString]
subComponents :: [ByteString]
}
deriving (SubComponents -> SubComponents -> Bool
(SubComponents -> SubComponents -> Bool)
-> (SubComponents -> SubComponents -> Bool) -> Eq SubComponents
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubComponents -> SubComponents -> Bool
== :: SubComponents -> SubComponents -> Bool
$c/= :: SubComponents -> SubComponents -> Bool
/= :: SubComponents -> SubComponents -> Bool
Eq, Int -> SubComponents -> ShowS
[SubComponents] -> ShowS
SubComponents -> String
(Int -> SubComponents -> ShowS)
-> (SubComponents -> String)
-> ([SubComponents] -> ShowS)
-> Show SubComponents
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubComponents -> ShowS
showsPrec :: Int -> SubComponents -> ShowS
$cshow :: SubComponents -> String
show :: SubComponents -> String
$cshowList :: [SubComponents] -> ShowS
showList :: [SubComponents] -> ShowS
Show, Eq SubComponents
Eq SubComponents =>
(SubComponents -> SubComponents -> Ordering)
-> (SubComponents -> SubComponents -> Bool)
-> (SubComponents -> SubComponents -> Bool)
-> (SubComponents -> SubComponents -> Bool)
-> (SubComponents -> SubComponents -> Bool)
-> (SubComponents -> SubComponents -> SubComponents)
-> (SubComponents -> SubComponents -> SubComponents)
-> Ord SubComponents
SubComponents -> SubComponents -> Bool
SubComponents -> SubComponents -> Ordering
SubComponents -> SubComponents -> SubComponents
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SubComponents -> SubComponents -> Ordering
compare :: SubComponents -> SubComponents -> Ordering
$c< :: SubComponents -> SubComponents -> Bool
< :: SubComponents -> SubComponents -> Bool
$c<= :: SubComponents -> SubComponents -> Bool
<= :: SubComponents -> SubComponents -> Bool
$c> :: SubComponents -> SubComponents -> Bool
> :: SubComponents -> SubComponents -> Bool
$c>= :: SubComponents -> SubComponents -> Bool
>= :: SubComponents -> SubComponents -> Bool
$cmax :: SubComponents -> SubComponents -> SubComponents
max :: SubComponents -> SubComponents -> SubComponents
$cmin :: SubComponents -> SubComponents -> SubComponents
min :: SubComponents -> SubComponents -> SubComponents
Ord, (forall x. SubComponents -> Rep SubComponents x)
-> (forall x. Rep SubComponents x -> SubComponents)
-> Generic SubComponents
forall x. Rep SubComponents x -> SubComponents
forall x. SubComponents -> Rep SubComponents x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SubComponents -> Rep SubComponents x
from :: forall x. SubComponents -> Rep SubComponents x
$cto :: forall x. Rep SubComponents x -> SubComponents
to :: forall x. Rep SubComponents x -> SubComponents
Generic)
data ComponentEdge = ComponentEdge
{ ComponentEdge -> ByteString
edgeClassComponent :: ByteString,
ComponentEdge -> ByteString
edgeSubComponent :: ByteString,
ComponentEdge -> ByteString
subComponentClass :: ByteString,
ComponentEdge -> Maybe ByteString
edgeLabel :: Maybe ByteString
}
deriving (ComponentEdge -> ComponentEdge -> Bool
(ComponentEdge -> ComponentEdge -> Bool)
-> (ComponentEdge -> ComponentEdge -> Bool) -> Eq ComponentEdge
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComponentEdge -> ComponentEdge -> Bool
== :: ComponentEdge -> ComponentEdge -> Bool
$c/= :: ComponentEdge -> ComponentEdge -> Bool
/= :: ComponentEdge -> ComponentEdge -> Bool
Eq, Int -> ComponentEdge -> ShowS
[ComponentEdge] -> ShowS
ComponentEdge -> String
(Int -> ComponentEdge -> ShowS)
-> (ComponentEdge -> String)
-> ([ComponentEdge] -> ShowS)
-> Show ComponentEdge
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComponentEdge -> ShowS
showsPrec :: Int -> ComponentEdge -> ShowS
$cshow :: ComponentEdge -> String
show :: ComponentEdge -> String
$cshowList :: [ComponentEdge] -> ShowS
showList :: [ComponentEdge] -> ShowS
Show, Eq ComponentEdge
Eq ComponentEdge =>
(ComponentEdge -> ComponentEdge -> Ordering)
-> (ComponentEdge -> ComponentEdge -> Bool)
-> (ComponentEdge -> ComponentEdge -> Bool)
-> (ComponentEdge -> ComponentEdge -> Bool)
-> (ComponentEdge -> ComponentEdge -> Bool)
-> (ComponentEdge -> ComponentEdge -> ComponentEdge)
-> (ComponentEdge -> ComponentEdge -> ComponentEdge)
-> Ord ComponentEdge
ComponentEdge -> ComponentEdge -> Bool
ComponentEdge -> ComponentEdge -> Ordering
ComponentEdge -> ComponentEdge -> ComponentEdge
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ComponentEdge -> ComponentEdge -> Ordering
compare :: ComponentEdge -> ComponentEdge -> Ordering
$c< :: ComponentEdge -> ComponentEdge -> Bool
< :: ComponentEdge -> ComponentEdge -> Bool
$c<= :: ComponentEdge -> ComponentEdge -> Bool
<= :: ComponentEdge -> ComponentEdge -> Bool
$c> :: ComponentEdge -> ComponentEdge -> Bool
> :: ComponentEdge -> ComponentEdge -> Bool
$c>= :: ComponentEdge -> ComponentEdge -> Bool
>= :: ComponentEdge -> ComponentEdge -> Bool
$cmax :: ComponentEdge -> ComponentEdge -> ComponentEdge
max :: ComponentEdge -> ComponentEdge -> ComponentEdge
$cmin :: ComponentEdge -> ComponentEdge -> ComponentEdge
min :: ComponentEdge -> ComponentEdge -> ComponentEdge
Ord, (forall x. ComponentEdge -> Rep ComponentEdge x)
-> (forall x. Rep ComponentEdge x -> ComponentEdge)
-> Generic ComponentEdge
forall x. Rep ComponentEdge x -> ComponentEdge
forall x. ComponentEdge -> Rep ComponentEdge x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ComponentEdge -> Rep ComponentEdge x
from :: forall x. ComponentEdge -> Rep ComponentEdge x
$cto :: forall x. Rep ComponentEdge x -> ComponentEdge
to :: forall x. Rep ComponentEdge x -> ComponentEdge
Generic)
graphVs :: (Monoid a) => [SubComponents] -> L.Graph a (ByteString, ByteString)
graphVs :: forall a.
Monoid a =>
[SubComponents] -> Graph a (ByteString, ByteString)
graphVs [SubComponents]
cs =
[(ByteString, ByteString)] -> Graph a (ByteString, ByteString)
forall e a. Monoid e => [a] -> Graph e a
L.vertices ([(ByteString, ByteString)] -> Graph a (ByteString, ByteString))
-> [(ByteString, ByteString)] -> Graph a (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$
((\ByteString
x -> (ByteString
x, ByteString
x)) (ByteString -> (ByteString, ByteString))
-> (SubComponents -> ByteString)
-> SubComponents
-> (ByteString, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Optic' A_Lens NoIx SubComponents ByteString
-> SubComponents -> ByteString
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx SubComponents ByteString
#classComponent (SubComponents -> (ByteString, ByteString))
-> [SubComponents] -> [(ByteString, ByteString)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SubComponents]
cs)
[(ByteString, ByteString)]
-> [(ByteString, ByteString)] -> [(ByteString, ByteString)]
forall a. Semigroup a => a -> a -> a
<> ([[(ByteString, ByteString)]] -> [(ByteString, ByteString)]
forall a. Monoid a => [a] -> a
mconcat ([[(ByteString, ByteString)]] -> [(ByteString, ByteString)])
-> [[(ByteString, ByteString)]] -> [(ByteString, ByteString)]
forall a b. (a -> b) -> a -> b
$ SubComponents -> [(ByteString, ByteString)]
subs (SubComponents -> [(ByteString, ByteString)])
-> [SubComponents] -> [[(ByteString, ByteString)]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SubComponents]
cs)
subs :: SubComponents -> [(ByteString, ByteString)]
subs :: SubComponents -> [(ByteString, ByteString)]
subs SubComponents
c = (Optic' A_Lens NoIx SubComponents ByteString
-> SubComponents -> ByteString
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx SubComponents ByteString
#classComponent SubComponents
c,) (ByteString -> (ByteString, ByteString))
-> [ByteString] -> [(ByteString, ByteString)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Optic' A_Lens NoIx SubComponents [ByteString]
-> SubComponents -> [ByteString]
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx SubComponents [ByteString]
#subComponents SubComponents
c
graphEs :: [ComponentEdge] -> L.Graph (Maybe ByteString) (ByteString, ByteString)
graphEs :: [ComponentEdge]
-> Graph (Maybe ByteString) (ByteString, ByteString)
graphEs [ComponentEdge]
es =
[(Maybe ByteString, (ByteString, ByteString),
(ByteString, ByteString))]
-> Graph (Maybe ByteString) (ByteString, ByteString)
forall e a. Monoid e => [(e, a, a)] -> Graph e a
L.edges ((\ComponentEdge
c -> (Optic' A_Lens NoIx ComponentEdge (Maybe ByteString)
-> ComponentEdge -> Maybe ByteString
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ComponentEdge (Maybe ByteString)
#edgeLabel ComponentEdge
c, (Optic' A_Lens NoIx ComponentEdge ByteString
-> ComponentEdge -> ByteString
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ComponentEdge ByteString
#edgeClassComponent ComponentEdge
c, Optic' A_Lens NoIx ComponentEdge ByteString
-> ComponentEdge -> ByteString
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ComponentEdge ByteString
#edgeSubComponent ComponentEdge
c), (Optic' A_Lens NoIx ComponentEdge ByteString
-> ComponentEdge -> ByteString
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ComponentEdge ByteString
#subComponentClass ComponentEdge
c, Optic' A_Lens NoIx ComponentEdge ByteString
-> ComponentEdge -> ByteString
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ComponentEdge ByteString
#subComponentClass ComponentEdge
c))) (ComponentEdge
-> (Maybe ByteString, (ByteString, ByteString),
(ByteString, ByteString)))
-> [ComponentEdge]
-> [(Maybe ByteString, (ByteString, ByteString),
(ByteString, ByteString))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ComponentEdge]
es)
graphAST :: [SubComponents] -> [ComponentEdge] -> L.Graph (Maybe ByteString) (ByteString, ByteString)
graphAST :: [SubComponents]
-> [ComponentEdge]
-> Graph (Maybe ByteString) (ByteString, ByteString)
graphAST [SubComponents]
cs [ComponentEdge]
es =
[SubComponents]
-> Graph (Maybe ByteString) (ByteString, ByteString)
forall a.
Monoid a =>
[SubComponents] -> Graph a (ByteString, ByteString)
graphVs [SubComponents]
cs Graph (Maybe ByteString) (ByteString, ByteString)
-> Graph (Maybe ByteString) (ByteString, ByteString)
-> Graph (Maybe ByteString) (ByteString, ByteString)
forall a. Semigroup a => a -> a -> a
<> [ComponentEdge]
-> Graph (Maybe ByteString) (ByteString, ByteString)
graphEs [ComponentEdge]
es
fromCEs :: [ComponentEdge] -> [SubComponents]
fromCEs :: [ComponentEdge] -> [SubComponents]
fromCEs [ComponentEdge]
es = ((ByteString, [ByteString]) -> SubComponents)
-> [(ByteString, [ByteString])] -> [SubComponents]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ByteString -> [ByteString] -> SubComponents)
-> (ByteString, [ByteString]) -> SubComponents
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ByteString -> [ByteString] -> SubComponents
SubComponents) ([(ByteString, [ByteString])] -> [SubComponents])
-> [(ByteString, [ByteString])] -> [SubComponents]
forall a b. (a -> b) -> a -> b
$ Map ByteString [ByteString] -> [(ByteString, [ByteString])]
forall k a. Map k a -> [(k, a)]
Map.toList (Map ByteString [ByteString] -> [(ByteString, [ByteString])])
-> Map ByteString [ByteString] -> [(ByteString, [ByteString])]
forall a b. (a -> b) -> a -> b
$ ([ByteString] -> [ByteString] -> [ByteString])
-> [(ByteString, [ByteString])] -> Map ByteString [ByteString]
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith [ByteString] -> [ByteString] -> [ByteString]
forall a. Semigroup a => a -> a -> a
(<>) ((\ComponentEdge
e -> (Optic' A_Lens NoIx ComponentEdge ByteString
-> ComponentEdge -> ByteString
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ComponentEdge ByteString
#edgeClassComponent ComponentEdge
e, [Optic' A_Lens NoIx ComponentEdge ByteString
-> ComponentEdge -> ByteString
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ComponentEdge ByteString
#edgeSubComponent ComponentEdge
e])) (ComponentEdge -> (ByteString, [ByteString]))
-> [ComponentEdge] -> [(ByteString, [ByteString])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ComponentEdge]
es)
recordNodes :: L.Graph (Maybe ByteString) (ByteString, ByteString) -> [Statement]
recordNodes :: Graph (Maybe ByteString) (ByteString, ByteString) -> [Statement]
recordNodes Graph (Maybe ByteString) (ByteString, ByteString)
g = (\(ByteString
s, [ByteString]
cs) -> NodeStatement -> Statement
StatementNode (NodeStatement -> Statement) -> NodeStatement -> Statement
forall a b. (a -> b) -> a -> b
$ ID -> Maybe Port -> Map ID ID -> NodeStatement
NodeStatement (ByteString -> ID
IDQuoted ByteString
s) Maybe Port
forall a. Maybe a
Nothing ([(ID, ID)] -> Map ID ID
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(ByteString -> ID
ID ByteString
"label", ByteString -> ID
IDQuoted ((ByteString, [ByteString]) -> ByteString
ls (ByteString
s, [ByteString]
cs)))] [(ID, ID)] -> [(ID, ID)] -> [(ID, ID)]
forall a. Semigroup a => a -> a -> a
<> [(ID, ID)]
-> (ByteString -> [(ID, ID)]) -> Maybe ByteString -> [(ID, ID)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\ByteString
url -> [(ByteString -> ID
ID ByteString
"URL", ByteString -> ID
IDQuoted ByteString
url)]) (ByteString -> Maybe ByteString
toURL ByteString
s)))) ((ByteString, [ByteString]) -> Statement)
-> [(ByteString, [ByteString])] -> [Statement]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(ByteString, [ByteString])]
supers
where
ls :: (ByteString, [ByteString]) -> ByteString
ls (ByteString
s, [ByteString]
cs) = ByteString -> [ByteString] -> ByteString
B.intercalate ByteString
"|" ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$ (ByteString
"<x" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
s ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"> " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
s) ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ByteString
y -> ByteString
" <x" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
y ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"> " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
y) [ByteString]
cs
supers :: [(ByteString, [ByteString])]
supers = (\(ByteString
s, [ByteString]
cs) -> (ByteString
s, (ByteString -> Bool) -> [ByteString] -> [ByteString]
forall a. (a -> Bool) -> [a] -> [a]
filter (ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
/= ByteString
s) [ByteString]
cs)) ((ByteString, [ByteString]) -> (ByteString, [ByteString]))
-> [(ByteString, [ByteString])] -> [(ByteString, [ByteString])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Map ByteString [ByteString] -> [(ByteString, [ByteString])]
forall k a. Map k a -> [(k, a)]
Map.toList (Map ByteString [ByteString] -> [(ByteString, [ByteString])])
-> Map ByteString [ByteString] -> [(ByteString, [ByteString])]
forall a b. (a -> b) -> a -> b
$ ([ByteString] -> [ByteString] -> [ByteString])
-> [(ByteString, [ByteString])] -> Map ByteString [ByteString]
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
(++) ((\(ByteString
s, ByteString
c) -> (ByteString
s, [ByteString
c])) ((ByteString, ByteString) -> (ByteString, [ByteString]))
-> [(ByteString, ByteString)] -> [(ByteString, [ByteString])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Graph (Maybe ByteString) (ByteString, ByteString)
-> [(ByteString, ByteString)]
forall a e. Ord a => Graph e a -> [a]
L.vertexList Graph (Maybe ByteString) (ByteString, ByteString)
g))
recordEdges :: Directed -> L.Graph (Maybe ByteString) (ByteString, ByteString) -> [Statement]
recordEdges :: Directed
-> Graph (Maybe ByteString) (ByteString, ByteString) -> [Statement]
recordEdges Directed
d Graph (Maybe ByteString) (ByteString, ByteString)
g =
( \(Maybe ByteString
l, (ByteString
s0, ByteString
c0), (ByteString
s1, ByteString
c1)) ->
EdgeStatement -> Statement
StatementEdge (EdgeStatement -> Statement) -> EdgeStatement -> Statement
forall a b. (a -> b) -> a -> b
$
EdgeOp -> EdgeID -> NonEmpty EdgeID -> Map ID ID -> EdgeStatement
EdgeStatement
(Directed -> EdgeOp
fromDirected Directed
d)
(ID -> Maybe Port -> EdgeID
EdgeID (ByteString -> ID
IDQuoted ByteString
s0) (Port -> Maybe Port
forall a. a -> Maybe a
Just (These ID Compass -> Port
Port (ID -> These ID Compass
forall a b. a -> These a b
This (ByteString -> ID
IDQuoted (ByteString
"x" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
c0))))))
([EdgeID] -> NonEmpty EdgeID
forall a. HasCallStack => [a] -> NonEmpty a
fromList [ID -> Maybe Port -> EdgeID
EdgeID (ByteString -> ID
IDQuoted ByteString
c1) (Port -> Maybe Port
forall a. a -> Maybe a
Just (These ID Compass -> Port
Port (ID -> These ID Compass
forall a b. a -> These a b
This (ByteString -> ID
IDQuoted (ByteString
"x" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
s1)))))])
([(ID, ID)] -> Map ID ID
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ByteString -> ID
ID ByteString
"label", ByteString -> ID
IDQuoted (ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ByteString
"x" Maybe ByteString
l))])
)
((Maybe ByteString, (ByteString, ByteString),
(ByteString, ByteString))
-> Statement)
-> [(Maybe ByteString, (ByteString, ByteString),
(ByteString, ByteString))]
-> [Statement]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Graph (Maybe ByteString) (ByteString, ByteString)
-> [(Maybe ByteString, (ByteString, ByteString),
(ByteString, ByteString))]
forall e a. (Eq e, Monoid e, Ord a) => Graph e a -> [(e, a, a)]
L.edgeList Graph (Maybe ByteString) (ByteString, ByteString)
g
toStatementsRecord :: Directed -> L.Graph (Maybe ByteString) (ByteString, ByteString) -> [Statement]
toStatementsRecord :: Directed
-> Graph (Maybe ByteString) (ByteString, ByteString) -> [Statement]
toStatementsRecord Directed
d Graph (Maybe ByteString) (ByteString, ByteString)
g =
Directed
-> Graph (Maybe ByteString) (ByteString, ByteString) -> [Statement]
recordEdges Directed
d Graph (Maybe ByteString) (ByteString, ByteString)
g [Statement] -> [Statement] -> [Statement]
forall a. Semigroup a => a -> a -> a
<> Graph (Maybe ByteString) (ByteString, ByteString) -> [Statement]
recordNodes Graph (Maybe ByteString) (ByteString, ByteString)
g
toURL :: ByteString -> Maybe ByteString
toURL :: ByteString -> Maybe ByteString
toURL ByteString
name = (ItemModule -> ByteString) -> Maybe ItemModule -> Maybe ByteString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ItemModule
i' -> [i|https://hackage.haskell.org/package/#{view #itemPackage i'}/docs/#{view #itemModule i'}.html\#t:#{view #item i'}|]) Maybe ItemModule
item
where
item :: Maybe ItemModule
item = (ItemModule -> Bool) -> [ItemModule] -> Maybe ItemModule
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
List.find ((ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
name) (ByteString -> Bool)
-> (ItemModule -> ByteString) -> ItemModule -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Optic' A_Lens NoIx ItemModule ByteString
-> ItemModule -> ByteString
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ItemModule ByteString
#item) [ItemModule]
itemModules
dotAST :: [SubComponents] -> [ComponentEdge] -> Graph
dotAST :: [SubComponents] -> [ComponentEdge] -> Graph
dotAST [SubComponents]
sc [ComponentEdge]
ce =
Graph
defaultGraph
Graph -> (Graph -> Graph) -> Graph
forall a b. a -> (a -> b) -> b
& Optic A_Lens NoIx Graph Graph (Maybe ID) (Maybe ID)
-> Maybe ID -> Graph -> Graph
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set (AttributeType
-> ID -> Optic A_Lens NoIx Graph Graph (Maybe ID) (Maybe ID)
attL AttributeType
GraphType (ByteString -> ID
ID ByteString
"size")) (ID -> Maybe ID
forall a. a -> Maybe a
Just (ID -> Maybe ID) -> ID -> Maybe ID
forall a b. (a -> b) -> a -> b
$ ByteString -> ID
IDQuoted ByteString
"5")
Graph -> (Graph -> Graph) -> Graph
forall a b. a -> (a -> b) -> b
& [Statement] -> Graph -> Graph
addStatements (Directed
-> Graph (Maybe ByteString) (ByteString, ByteString) -> [Statement]
toStatementsRecord Directed
Directed ([SubComponents]
-> [ComponentEdge]
-> Graph (Maybe ByteString) (ByteString, ByteString)
graphAST [SubComponents]
sc [ComponentEdge]
ce))
Graph -> (Graph -> Graph) -> Graph
forall a b. a -> (a -> b) -> b
& AttributeType
-> ID -> Optic A_Lens NoIx Graph Graph (Maybe ID) (Maybe ID)
attL AttributeType
NodeType (ByteString -> ID
ID ByteString
"shape")
Optic A_Lens NoIx Graph Graph (Maybe ID) (Maybe ID)
-> Maybe ID -> Graph -> Graph
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ ID -> Maybe ID
forall a. a -> Maybe a
Just (ByteString -> ID
ID ByteString
"record")
Graph -> (Graph -> Graph) -> Graph
forall a b. a -> (a -> b) -> b
& ID -> Optic A_Lens NoIx Graph Graph (Maybe ID) (Maybe ID)
gattL (ByteString -> ID
ID ByteString
"rankdir")
Optic A_Lens NoIx Graph Graph (Maybe ID) (Maybe ID)
-> Maybe ID -> Graph -> Graph
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ ID -> Maybe ID
forall a. a -> Maybe a
Just (ByteString -> ID
IDQuoted ByteString
"LR")
data ItemModule = ItemModule {ItemModule -> ByteString
item :: ByteString, ItemModule -> ByteString
itemModule :: ByteString, ItemModule -> ByteString
itemPackage :: ByteString} deriving (ItemModule -> ItemModule -> Bool
(ItemModule -> ItemModule -> Bool)
-> (ItemModule -> ItemModule -> Bool) -> Eq ItemModule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ItemModule -> ItemModule -> Bool
== :: ItemModule -> ItemModule -> Bool
$c/= :: ItemModule -> ItemModule -> Bool
/= :: ItemModule -> ItemModule -> Bool
Eq, Int -> ItemModule -> ShowS
[ItemModule] -> ShowS
ItemModule -> String
(Int -> ItemModule -> ShowS)
-> (ItemModule -> String)
-> ([ItemModule] -> ShowS)
-> Show ItemModule
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ItemModule -> ShowS
showsPrec :: Int -> ItemModule -> ShowS
$cshow :: ItemModule -> String
show :: ItemModule -> String
$cshowList :: [ItemModule] -> ShowS
showList :: [ItemModule] -> ShowS
Show, (forall x. ItemModule -> Rep ItemModule x)
-> (forall x. Rep ItemModule x -> ItemModule) -> Generic ItemModule
forall x. Rep ItemModule x -> ItemModule
forall x. ItemModule -> Rep ItemModule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ItemModule -> Rep ItemModule x
from :: forall x. ItemModule -> Rep ItemModule x
$cto :: forall x. Rep ItemModule x -> ItemModule
to :: forall x. Rep ItemModule x -> ItemModule
Generic)
itemModules :: [ItemModule]
itemModules :: [ItemModule]
itemModules =
[ ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"ChartOptions" ByteString
"Chart-Markup" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"MarkupOptions" ByteString
"Chart-Markup" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"CssOptions" ByteString
"Chart-Markup" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"ChartTree" ByteString
"Chart-Primitive" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Chart" ByteString
"Chart-Primitive" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"HudOptions" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"RenderStyle" ByteString
"Chart-Markup" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"ChartAspect" ByteString
"Chart-Primitive" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"ShapeRendering" ByteString
"Chart-Markup" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"PreferColorScheme" ByteString
"Chart-Primitive" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Tree" ByteString
"Data-Tree" ByteString
"containers",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Priority" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"TitleOptions" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"AxisOptions" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"LegendOptions" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"FrameOptions" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Adjustments" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Ticks" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Tick" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Place" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"TickStyle" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"AxisBar" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"HudChartSection" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"TickExtend" ByteString
"Chart-Hud" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"FormatN" ByteString
"Data-FormatN" ByteString
"formatn",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"FStyle" ByteString
"Data-FormatN" ByteString
"formatn",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Colour" ByteString
"Data-Colour" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Style" ByteString
"Chart-Style" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"EscapeText" ByteString
"Chart-Style" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"GlyphShape" ByteString
"Chart-Style" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Anchor" ByteString
"Chart-Style" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"LineCap" ByteString
"Chart-Style" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"LineJoin" ByteString
"Chart-Style" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"ScaleP" ByteString
"Chart-Style" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"ChartData" ByteString
"Chart-Primitive" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"PathData" ByteString
"Data-Path" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"ArcInfo" ByteString
"Data-Path" ByteString
"chart-svg",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Rect" ByteString
"NumHask-Space-Rect" ByteString
"numhask-space",
ByteString -> ByteString -> ByteString -> ItemModule
ItemModule ByteString
"Point" ByteString
"NumHask-Space-Point" ByteString
"numhask-space"
]
componentEdges :: [ComponentEdge]
componentEdges :: [ComponentEdge]
componentEdges =
[ ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"ChartOptions" ByteString
"markupOptions" ByteString
"MarkupOptions" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"ChartOptions" ByteString
"hudOptions" ByteString
"HudOptions" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"ChartOptions" ByteString
"chartTree" ByteString
"ChartTree" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"MarkupOptions" ByteString
"chartAspect" ByteString
"ChartAspect" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"MarkupOptions" ByteString
"cssOptions" ByteString
"CssOptions" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"MarkupOptions" ByteString
"renderStyle" ByteString
"RenderStyle" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"CssOptions" ByteString
"shapeRendering" ByteString
"ShapeRendering" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"CssOptions" ByteString
"preferColorScheme" ByteString
"PreferColorScheme" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"HudOptions" ByteString
"axes" ByteString
"AxisOptions" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"each % #item"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"HudOptions" ByteString
"frames" ByteString
"FrameOptions" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"each % #item"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"HudOptions" ByteString
"legends" ByteString
"LegendOptions" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"each % #item"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"HudOptions" ByteString
"titles" ByteString
"TitleOptions" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"each % #item"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"HudOptions" ByteString
"axes" ByteString
"Priority" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"each % #priority"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"HudOptions" ByteString
"frames" ByteString
"Priority" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"each % #priority"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"HudOptions" ByteString
"legends" ByteString
"Priority" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"each % #priority"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"HudOptions" ByteString
"titles" ByteString
"Priority" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"each % #priority"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"AxisOptions" ByteString
"axisBar" ByteString
"AxisBar" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"AxisOptions" ByteString
"adjustments" ByteString
"Adjustments" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"AxisOptions" ByteString
"ticks" ByteString
"Ticks" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"AxisOptions" ByteString
"place" ByteString
"Place" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"AxisBar" ByteString
"style" ByteString
"Style" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"AxisBar" ByteString
"anchorTo" ByteString
"HudChartSection" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Tick" ByteString
"formatN'" ByteString
"FormatN" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"FormatN" ByteString
"fstyle" ByteString
"FStyle" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Tick" ByteString
"tickExtend'" ByteString
"TickExtend" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Ticks" ByteString
"tick" ByteString
"Tick" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Ticks" ByteString
"glyphTick" ByteString
"TickStyle" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Ticks" ByteString
"textTick" ByteString
"TickStyle" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Ticks" ByteString
"lineTick" ByteString
"TickStyle" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"TickStyle" ByteString
"style" ByteString
"Style" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"TickStyle" ByteString
"anchorTo" ByteString
"HudChartSection" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"FrameOptions" ByteString
"frame" ByteString
"Style" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"#frame % _Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"FrameOptions" ByteString
"anchorTo" ByteString
"HudChartSection" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"TitleOptions" ByteString
"style" ByteString
"Style" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"TitleOptions" ByteString
"place" ByteString
"Place" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"TitleOptions" ByteString
"anchor" ByteString
"Anchor" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"ChartTree" ByteString
"tree" ByteString
"Tree" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"ChartTree" ByteString
"charts'" ByteString
"Chart" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"each"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Chart" ByteString
"chartStyle" ByteString
"Style" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Chart" ByteString
"chartData" ByteString
"ChartData" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"ChartData" ByteString
"rectData'" ByteString
"Rect" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just % each"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"ChartData" ByteString
"lineData'" ByteString
"Point" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just % each % each"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"ChartData" ByteString
"glyphData'" ByteString
"Point" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just % each"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"ChartData" ByteString
"textData'" ByteString
"(Text,Point)" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just % each"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"(Text,Point)" ByteString
"_2" ByteString
"Point" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"ChartData" ByteString
"pathData'" ByteString
"PathData" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just % each"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"ChartData" ByteString
"blankData'" ByteString
"Rect" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just % each"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"LegendOptions" ByteString
"textStyle" ByteString
"Style" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"LegendOptions" ByteString
"frame" ByteString
"Style" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"LegendOptions" ByteString
"place" ByteString
"Place" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"LegendOptions" ByteString
"scaleP" ByteString
"ScaleP" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"LegendOptions" ByteString
"legendCharts" ByteString
"Chart" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"each % _2 % each"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"PathData" ByteString
"ArcP" ByteString
"ArcInfo" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"(ArcP arcinfo _)"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Style" ByteString
"color" ByteString
"Colour" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Style" ByteString
"borderColor" ByteString
"Colour" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Style" ByteString
"scaleP" ByteString
"ScaleP" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Style" ByteString
"anchor" ByteString
"Anchor" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Style" ByteString
"translate" ByteString
"Point" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Style" ByteString
"escapeText" ByteString
"EscapeText" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
""),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Style" ByteString
"frame" ByteString
"Style" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Style" ByteString
"lineCap" ByteString
"LineCap" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Style" ByteString
"lineJoin" ByteString
"LineJoin" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"_Just"),
ByteString
-> ByteString -> ByteString -> Maybe ByteString -> ComponentEdge
ComponentEdge ByteString
"Style" ByteString
"glyphShape" ByteString
"GlyphShape" (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"")
]
allSC :: [SubComponents]
allSC :: [SubComponents]
allSC =
[ SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"AxisBar",
subComponents :: [ByteString]
subComponents =
[ ByteString
"style",
ByteString
"size",
ByteString
"buffer",
ByteString
"overhang",
ByteString
"anchorTo"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"AxisOptions",
subComponents :: [ByteString]
subComponents =
[ ByteString
"axisBar",
ByteString
"adjustments",
ByteString
"ticks",
ByteString
"place"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"Chart",
subComponents :: [ByteString]
subComponents =
[ ByteString
"chartStyle",
ByteString
"chartData"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"ChartData",
subComponents :: [ByteString]
subComponents =
[ ByteString
"rectData'",
ByteString
"lineData'",
ByteString
"glyphData'",
ByteString
"textData'",
ByteString
"pathData'",
ByteString
"blankData'"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"ChartOptions",
subComponents :: [ByteString]
subComponents =
[ ByteString
"markupOptions",
ByteString
"hudOptions",
ByteString
"chartTree"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"ChartTree",
subComponents :: [ByteString]
subComponents =
[ ByteString
"tree",
ByteString
"charts'"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"FrameOptions",
subComponents :: [ByteString]
subComponents =
[ ByteString
"frame",
ByteString
"anchorTo",
ByteString
"buffer"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"HudOptions",
subComponents :: [ByteString]
subComponents =
[ ByteString
"axes",
ByteString
"frames",
ByteString
"legends",
ByteString
"titles"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"MarkupOptions",
subComponents :: [ByteString]
subComponents =
[ ByteString
"markupHeight",
ByteString
"chartAspect",
ByteString
"cssOptions",
ByteString
"renderStyle"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"(Text,Point)",
subComponents :: [ByteString]
subComponents =
[ ByteString
"_1",
ByteString
"_2"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"TickStyle",
subComponents :: [ByteString]
subComponents =
[ ByteString
"style",
ByteString
"anchorTo",
ByteString
"buffer"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"Ticks",
subComponents :: [ByteString]
subComponents =
[ ByteString
"tick",
ByteString
"glyphTick",
ByteString
"textTick",
ByteString
"lineTick"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"TitleOptions",
subComponents :: [ByteString]
subComponents =
[ ByteString
"text",
ByteString
"style",
ByteString
"place",
ByteString
"anchor",
ByteString
"buffer"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"RenderStyle",
subComponents :: [ByteString]
subComponents =
[ ByteString
"Compact",
ByteString
"Indented"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"CssOptions",
subComponents :: [ByteString]
subComponents =
[ ByteString
"shapeRendering",
ByteString
"preferColorScheme",
ByteString
"fontFamilies",
ByteString
"cssExtra"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"ChartAspect",
subComponents :: [ByteString]
subComponents =
[ ByteString
"FixedAspect",
ByteString
"CanvasAspect",
ByteString
"ChartAspect",
ByteString
"UnscaledAspect"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"HudChartSection",
subComponents :: [ByteString]
subComponents =
[ ByteString
"CanvasSection",
ByteString
"CanvasStyleSection",
ByteString
"HudSection",
ByteString
"HudStyleSection"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"Adjustments",
subComponents :: [ByteString]
subComponents =
[ ByteString
"maxXRatio",
ByteString
"maxYRatio",
ByteString
"angledRatio",
ByteString
"allowDiagonal"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"Tick",
subComponents :: [ByteString]
subComponents =
[ ByteString
"TickNone",
ByteString
"TickLabels",
ByteString
"TickRound",
ByteString
"TickExact",
ByteString
"TickPlaced",
ByteString
"numTicks'",
ByteString
"formatN'",
ByteString
"tickExtend'"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"TickExtend",
subComponents :: [ByteString]
subComponents =
[ ByteString
"TickExtend",
ByteString
"NoTickExtend"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"FStyle",
subComponents :: [ByteString]
subComponents =
[ ByteString
"FSDecimal",
ByteString
"FSExponent",
ByteString
"FSComma",
ByteString
"FSFixed Int",
ByteString
"FSPercent",
ByteString
"FSDollar",
ByteString
"FSPrec",
ByteString
"FSCommaPrec",
ByteString
"FSNone"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"FormatN",
subComponents :: [ByteString]
subComponents =
[ ByteString
"fstyle",
ByteString
"sigFigs",
ByteString
"maxDistinguishIterations",
ByteString
"addLPad",
ByteString
"cutRightZeros"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"ShapeRendering",
subComponents :: [ByteString]
subComponents =
[ ByteString
"UseGeometricPrecision",
ByteString
"UseCssCrisp",
ByteString
"NoShapeRendering"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"PreferColorScheme",
subComponents :: [ByteString]
subComponents =
[ ByteString
"PreferHud",
ByteString
"PreferDark",
ByteString
"PreferLight",
ByteString
"PreferNormal"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"Place",
subComponents :: [ByteString]
subComponents =
[ ByteString
"PlaceLeft",
ByteString
"PlaceRight",
ByteString
"PlaceTop",
ByteString
"PlaceBottom",
ByteString
"PlaceAbsolute"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"LegendOptions",
subComponents :: [ByteString]
subComponents =
[ ByteString
"legendSize",
ByteString
"buffer",
ByteString
"vgap",
ByteString
"hgap",
ByteString
"textStyle",
ByteString
"innerPad",
ByteString
"outerPad",
ByteString
"frame",
ByteString
"place",
ByteString
"scaleChartsBy",
ByteString
"scaleP",
ByteString
"legendCharts"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"Anchor",
subComponents :: [ByteString]
subComponents =
[ ByteString
"AnchorMiddle",
ByteString
"AnchorStart",
ByteString
"AnchorEnd"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"Point",
subComponents :: [ByteString]
subComponents =
[ ByteString
"_x",
ByteString
"_y"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"PathData",
subComponents :: [ByteString]
subComponents =
[ ByteString
"StartP",
ByteString
"LineP",
ByteString
"CubicP",
ByteString
"QuadP",
ByteString
"ArcP"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"ArcInfo",
subComponents :: [ByteString]
subComponents =
[ ByteString
"radii",
ByteString
"phi",
ByteString
"large",
ByteString
"clockwise"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"Style",
subComponents :: [ByteString]
subComponents =
[ ByteString
"size",
ByteString
"borderSize",
ByteString
"color",
ByteString
"borderColor",
ByteString
"scaleP",
ByteString
"anchor",
ByteString
"rotation",
ByteString
"translate",
ByteString
"escapeText",
ByteString
"frame",
ByteString
"lineCap",
ByteString
"lineJoin",
ByteString
"dasharray",
ByteString
"dashoffset",
ByteString
"hsize",
ByteString
"vsize",
ByteString
"vshift",
ByteString
"glyphShape"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"ScaleP",
subComponents :: [ByteString]
subComponents =
[ ByteString
"NoScaleP",
ByteString
"ScalePX",
ByteString
"ScalePY",
ByteString
"ScalePMinDim",
ByteString
"ScalePArea"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"Colour",
subComponents :: [ByteString]
subComponents =
[ ByteString
"opac'",
ByteString
"lightness'",
ByteString
"chroma'",
ByteString
"hue'"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"EscapeText",
subComponents :: [ByteString]
subComponents =
[ ByteString
"EscapeText",
ByteString
"NoEscapeText"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"LineCap",
subComponents :: [ByteString]
subComponents =
[ ByteString
"LineCapButt",
ByteString
"LineCapRound",
ByteString
"LineCapSquare"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"LineJoin",
subComponents :: [ByteString]
subComponents =
[ ByteString
"LineJoinMiter",
ByteString
"LineJoinBevel",
ByteString
"LineJoinRound"
]
},
SubComponents
{ classComponent :: ByteString
classComponent = ByteString
"GlyphShape",
subComponents :: [ByteString]
subComponents =
[ ByteString
"CircleGlyph",
ByteString
"SquareGlyph",
ByteString
"EllipseGlyph",
ByteString
"RectSharpGlyph",
ByteString
"RectRoundedGlyph",
ByteString
"TriangleGlyph",
ByteString
"VLineGlyph",
ByteString
"HLineGlyph",
ByteString
"PathGlyph"
]
}
]