dotparse-0.1.0.0: dot language parsing and printing.
Safe HaskellSafe-Inferred
LanguageGHC2021

DotParse.Examples.AST

Description

Example of Dot graph construction for the chart-svg class heirarchy.

Synopsis

Documentation

>>> import DotParse
>>> :set -XOverloadedStrings

data SubComponents Source #

A Haskell class and (informal) list of sub-components.

Instances

Instances details
Generic SubComponents Source # 
Instance details

Defined in DotParse.Examples.AST

Associated Types

type Rep SubComponents :: Type -> Type #

Show SubComponents Source # 
Instance details

Defined in DotParse.Examples.AST

Eq SubComponents Source # 
Instance details

Defined in DotParse.Examples.AST

Ord SubComponents Source # 
Instance details

Defined in DotParse.Examples.AST

type Rep SubComponents Source # 
Instance details

Defined in DotParse.Examples.AST

type Rep SubComponents = D1 ('MetaData "SubComponents" "DotParse.Examples.AST" "dotparse-0.1.0.0-Glh386MQdGkE2gsLJXwO3r" 'False) (C1 ('MetaCons "SubComponents" 'PrefixI 'True) (S1 ('MetaSel ('Just "classComponent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "subComponents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ByteString])))

data ComponentEdge Source #

Relationship between a class, a sub-component and the class of the sub-component.

Instances

Instances details
Generic ComponentEdge Source # 
Instance details

Defined in DotParse.Examples.AST

Associated Types

type Rep ComponentEdge :: Type -> Type #

Show ComponentEdge Source # 
Instance details

Defined in DotParse.Examples.AST

Eq ComponentEdge Source # 
Instance details

Defined in DotParse.Examples.AST

Ord ComponentEdge Source # 
Instance details

Defined in DotParse.Examples.AST

type Rep ComponentEdge Source # 
Instance details

Defined in DotParse.Examples.AST

type Rep ComponentEdge = D1 ('MetaData "ComponentEdge" "DotParse.Examples.AST" "dotparse-0.1.0.0-Glh386MQdGkE2gsLJXwO3r" 'False) (C1 ('MetaCons "ComponentEdge" 'PrefixI 'True) ((S1 ('MetaSel ('Just "edgeClassComponent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "edgeSubComponent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :*: (S1 ('MetaSel ('Just "subComponentClass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "edgeLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ByteString)))))

graphVs :: Monoid a => [SubComponents] -> Graph a (ByteString, ByteString) Source #

algebraic graph vertices

subs :: SubComponents -> [(ByteString, ByteString)] Source #

Convert sub-components to a list of class, subcomponent bytestring tuples.

fromCEs :: [ComponentEdge] -> [SubComponents] Source #

Create a list of SubComponents from a list of ComponentEdges

recordNodes :: Graph (Maybe ByteString) (ByteString, ByteString) -> [Statement] Source #

Convert an algebraic Graph into dot record nodes

recordEdges :: Directed -> Graph (Maybe ByteString) (ByteString, ByteString) -> [Statement] Source #

Convert an algebraic Graph into dot edges

toURL :: ByteString -> Maybe ByteString Source #

Convert a node ID to a label for chart-svg charts Doing this directly in dot doesn't quite work because the engines get the width of the link wrong.

dotAST :: [SubComponents] -> [ComponentEdge] -> Graph Source #

AST Graph

gAST = dotAST allSC componentEdges
C.writeFile "other/ast.dot" $ dotPrint defaultDotConfig gAST
bsSvg <- processDotWith Directed ["-Tsvg"] (dotPrint defaultDotConfig gAST)
C.writeFile "other/ast.svg" bsSvg

data ItemModule Source #

Link values

Instances

Instances details
Generic ItemModule Source # 
Instance details

Defined in DotParse.Examples.AST

Associated Types

type Rep ItemModule :: Type -> Type #

Show ItemModule Source # 
Instance details

Defined in DotParse.Examples.AST

Eq ItemModule Source # 
Instance details

Defined in DotParse.Examples.AST

type Rep ItemModule Source # 
Instance details

Defined in DotParse.Examples.AST

type Rep ItemModule = D1 ('MetaData "ItemModule" "DotParse.Examples.AST" "dotparse-0.1.0.0-Glh386MQdGkE2gsLJXwO3r" 'False) (C1 ('MetaCons "ItemModule" 'PrefixI 'True) (S1 ('MetaSel ('Just "item") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: (S1 ('MetaSel ('Just "itemModule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "itemPackage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))))

itemModules :: [ItemModule] Source #

List of link values

componentEdges :: [ComponentEdge] Source #

list of chart-svg component edges

allSC :: [SubComponents] Source #

list of chart-svg subcomponents