1/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    2    digraph_to_plantuml -- Creates UML class diagrams from Python pylint's pyreverse generated .dot files.
    3    Written Apr. 29th, 2022 by Conrado M. Rodriguez <Conrado.Rgz@gmail.com>
    4    Public domain code.        https://github.com/crgz
    5- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
    6:-module(py_to_plantuml, [digraph_to_plantuml/1, digraph/3]).    7:- use_module(library(dcg/basics)).    8:- set_portray_text(enabled, true).
 digraph_to_plantuml(+Files)
True if UML class diagrams can be parsed from Python pylint's pyreverse generated .dot files.
digraph_to_plantuml(Files).
   17digraph_to_plantuml([]).
   18digraph_to_plantuml([Head|Tail]) :- write_plantuml(Head), digraph_to_plantuml(Tail).
   19
   20write_plantuml(File):-
   21   phrase_from_file(digraph(digraph(GraphNameCodes, Entries)), File),
   22   atom_codes(GraphName, GraphNameCodes), %print_term(digraph(GraphName,Entries), []),
   23   atom_concat(GraphName, '.plantuml', OutputFileName),
   24   open(OutputFileName, write, Out),
   25   format(Out, '@startuml ~w\n', [GraphName]),
   26   write_lines(Out, Entries),
   27   format(Out, '@enduml\n', []),
   28   close(Out),!.
   29
   30write_lines(_,[]).
   31write_lines(Out,[Head|Tail]) :- write_line(Out,Head), write_lines(Out,Tail).
   32
   33write_line(Out,relationship(Super, Sub, Options)):-
   34   atom_codes(AtomicSuper, Super),
   35   atom_codes(AtomicSub, Sub),
   36   arrow(Options, Arrow),
   37   format(Out, '~w ~w ~w\n', [AtomicSuper, Arrow, AtomicSub]).
   38write_line(_,_).
   39
   40arrow(Options, ' <|-- '):-member(attribute(`arrowhead`,`empty`), Options).
   41arrow(Options, ' *-- '):-member(attribute(`arrowhead`,`diamond`), Options).
   42
   43digraph(digraph(FileName,Digraph)) --> "digraph", blanks, nonblanks(FileName), blanks, entry_list(Digraph).
   44
   45entry_list(Options) --> "{", empty_lines, entries(Options), "}", (empty_lines|eos).
   46
   47entries([]) --> [].
   48entries([W|Ws]) --> entry(W), !, entries(Ws).
   49
   50entry(graph(Options)) -->  
   51   blanks, "graph", 
   52   attribute_list(Options), ";", empty_lines.
   53entry(class(R, Options)) --> 
   54   blanks, class(R), 
   55   attribute_list(Options), ";", empty_lines.
   56entry(relationship(Super,Sub, Options)) --> 
   57   blanks, relationship(Super,Sub), 
   58   attribute_list(Options), ";", empty_lines.
   59
   60relationship(Super,Sub) --> class(Super), blanks, "->", blanks, class(Sub).
   61
   62class(Class) --> quoted_identifier(Class).
   63
   64attribute_list(Options) --> blanks, "[", attributes(Options), "]".
   65
   66attributes([]) --> [].
   67attributes([W]) --> attribute(W).
   68attributes([W|Ws]) --> attribute(W), ",", attributes(Ws).
   69
   70attribute(attribute(K, V)) --> maybe_quoted_identifier( K), "=", maybe_quoted_identifier(V).
   71
   72empty_lines --> blank, empty_lines, !.
   73empty_lines --> blank.
   74
   75maybe_quoted_identifier(Identifier) --> quoted_identifier(Identifier) | identifier(Identifier).
   76
   77quoted_identifier(Identifier) --> "\"", identifier(Identifier), "\"".
   78
   79identifier([A|As]) --> [A],
   80   { char_type(A, alpha) },
   81   symbol_r(As).
   82
   83symbol_r([A|As]) --> [A], 
   84   { valid_char(A) ; char_type(A, alnum) }, 
   85   symbol_r(As).
   86symbol_r([])     --> [].
   87
   88valid_char(0'-)