1:- encoding(utf8).
    2:- module(
    3  dot_html,
    4  [
    5    dot_html//1 % +Spec
    6  ]
    7).

DOT HTML-like labels

Grammar taken from the GraphViz Web site:

cell: <TD> (text* | table | <IMG/>) </TD>
text : string
     | <BR/>
     | <FONT> text* </FONT>
     | <I> text* </I>
     | <B> text* </B>
     | <U> text* </U>
     | <O> text* </O>
     | <SUB> text* </SUB>
     | <SUP> text* </SUP>
     | <S> text* </S>
row: <TR> cell ((<VR/>)? cells)? </TR>
table : <FONT> table </FONT>
      | <TABLE> (row (<HR/>)?)* </TABLE>
See also
- http://www.graphviz.org/content/node-shapes#html

*/

   34:- use_module(library(error)).   35
   36:- use_module(library(abnf)).   37:- use_module(library(dcg)).   38:- use_module(library(dcg_html)).   39:- use_module(library(dot)).
 dot_html(+Spec:compound)// is det
   47% b
   48dot_html(b(Spec)) --> !,
   49  html_element(b, [], dot_html:dot_html(Spec)).
   50% br
   51% - `ALIGN="CENTER|LEFT|RIGHT"`
   52dot_html(br) --> !,
   53  dot_html(br([])).
   54dot_html(br(Attrs0)) --> !,
   55  {attributes_(Attrs0, Attrs)},
   56  html_element(br, Attrs, "").
   57% cell
   58% - `ALIGN="CENTER|LEFT|RIGHT|TEXT"`
   59% - `BALIGN="CENTER|LEFT|RIGHT"`
   60% - `BGCOLOR="color"`
   61% - `BORDER="value"`
   62% - `CELLPADDING="value"`
   63% - `CELLSPACING="value"`
   64% - `COLOR="color"`
   65% - `COLSPAN="value"`
   66% - `FIXEDSIZE="FALSE|TRUE"`
   67% - `GRADIENTANGLE="value"`
   68% - `HEIGHT="value"`
   69% - `HREF="value"`
   70% - `ID="value"`
   71% - `PORT="portName"`
   72% - `ROWSPAN="value"`
   73% - `SIDES="value"`
   74% - `STYLE="value"`
   75% - `TARGET="value"`
   76% - `TITLE="value"`
   77% - `TOOLTIP="value"`
   78% - `VALIGN="MIDDLE|BOTTOM|TOP"`
   79% - `WIDTH="value"`
   80dot_html(cell(Attrs0,Spec)) --> !,
   81  {attributes_(Attrs0, Attrs)},
   82  html_element(td, Attrs, dot_html:dot_html(Spec)).
   83dot_html(cell(Spec)) --> !,
   84  dot_html(cell([],Spec)).
   85% font
   86% - `COLOR="color"`
   87%   Sets the color of the font within the scope of ‘<FONT>…</FONT>’,
   88%   or the border color of the table or cell within the scope of
   89%   ‘<TABLE>…</TABLE>’, or ‘<TD>…</TD>’.  This color can be overridden
   90%   by a ‘COLOR’ attribute in descendents.  By default, the font color
   91%   is determined by the ‘fontcolor’ attribute of the corresponding
   92%   node, edge or graph, and the border color is determined by the
   93%   color attribute of the corresponding node, edge or graph.
   94% - `FACE="fontname"`
   95% - `POINT-SIZE="value"`
   96dot_html(font(Attrs0,Spec)) --> !,
   97  {attributes_(Attrs0, Attrs)},
   98  html_element(font, Attrs, dot_html:dot_html(Spec)).
   99dot_html(font(Spec)) --> !,
  100  dot_html(font([],Spec)).
  101% i
  102dot_html(i(Spec)) --> !,
  103  html_element(i, [], dot_html:dot_html(Spec)).
  104% img
  105% - `SCALE="FALSE|TRUE|WIDTH|HEIGHT|BOTH"`
  106% - `SRC="value"`
  107dot_html(img(Attrs0)) --> !,
  108  {attributes_(Attrs0, Attrs)},
  109  html_element(img, Attrs).
  110% o
  111dot_html(o(Spec)) --> !,
  112  html_element(o, [], dot_html:dot_html(Spec)).
  113dot_html(row_([vr|T])) --> !,
  114  html_element(vr),
  115  dot_html(row_(T)).
  116dot_html(row_([H|T])) --> !,
  117  dot_html(H),
  118  dot_html(row_(T)).
  119dot_html(row_([])) --> !, "".
  120dot_html(rows_([hr|T])) --> !,
  121  html_element(hr),
  122  dot_html(rows_(T)).
  123dot_html(rows_([H|T])) --> !,
  124  html_element(tr, [], dot_html(row_(H))),
  125  dot_html(rows_(T)).
  126dot_html(rows_([])) --> !, "".
  127% s
  128dot_html(s(Spec)) --> !,
  129  html_element(s, [], dot_html:dot_html(Spec)).
  130% sub
  131dot_html(sub(Spec)) --> !,
  132  html_element(sub, [], dot_html:dot_html(Spec)).
  133% sup
  134dot_html(sup(Spec)) --> !,
  135  html_element(sup, [], dot_html:dot_html(Spec)).
  136% table
  137% - `ALIGN="CENTER|LEFT|RIGHT"`
  138% - `BGCOLOR="color"`
  139% - `BORDER="value"`
  140% - `CELLBORDER="value"`
  141% - `CELLPADDING="value"`
  142% - `CELLSPACING="value"`
  143% - `COLOR="color"`
  144% - `COLUMNS="value"`
  145% - `FIXEDSIZE="FALSE|TRUE"`
  146% - `GRADIENTANGLE="value"`
  147% - `HEIGHT="value"`
  148% - `HREF="value"`
  149% - `ID="value"`
  150% - `PORT="portName"`
  151% - `ROWS="value"`
  152% - `SIDES="value"`
  153% - `STYLE="value"`
  154% - `TARGET="value"`
  155% - `TITLE="value"`
  156% - `TOOLTIP="value"`
  157% - `VALIGN="MIDDLE|BOTTOM|TOP"`
  158% - `WIDTH="value"`
  159dot_html(table(Specs)) --> !,
  160  dot_html(table([],Specs)).
  161dot_html(table(Attrs0,Rows)) --> !,
  162  {attributes_(Attrs0, Attrs)},
  163  html_element(table, Attrs, dot_html:dot_html(rows_(Rows))).
  164% u
  165dot_html(u(Spec)) --> !,
  166  html_element(u, [], dot_html:dot_html(Spec)).
  167dot_html([]) --> !, "".
  168dot_html([H|T]) --> !,
  169  dot_html(H),
  170  dot_html(T).
  171dot_html(String) -->
  172  {string(String)}, !,
  173  {dot_html_replace(String, EscapedString)},
  174  atom(EscapedString).
  175% error
  176dot_html(Spec) -->
  177  syntax_error(dot_html_like_label(Spec)).
  178
  179attributes_(Attrs, Attrs) :-
  180  is_list(Attrs), !.
  181attributes_(Attr, [Attr])