1:- module(
    2  dcg_html,
    3  [
    4    dcg_html//1,       % +Content
    5    html_attribute//1, % +Attribute
    6    html_element//1,   % +Name
    7    html_element//2,   % +Name, +Attributes
    8    html_element//3,   % +Name, +Attributes, :Content_0
    9    html_entity//1,    % +Name
   10    html_graphic//1,   % +Code
   11    html_string//1,    % +String
   12    html_style//1      % +Pair
   13  ]
   14).

DCG grammar for generating HTML snippets

*/

   20:- use_module(library(abnf)).   21:- use_module(library(dcg)).   22
   23:- meta_predicate
   24    html_element(+, +, //, ?, ?).
 html_attribute(+Attribute:compound)// is det
   32html_attribute(Attr) -->
   33  {
   34    compound_name_arguments(Attr, Name0, [Arg]),
   35    upcase_atom(Name0, Name)
   36  },
   37  " ",
   38  atom(Name),
   39  "=\"",
   40  html_string(Arg),
   41  "\"".
 dcg_html(+Content:list(compound))// is det
   47% Tag with no content.
   48dcg_html([tag(Name,Attrs)|T]) --> !,
   49  html_element(Name, Attrs),
   50  dcg_html(T).
   51% Tag with content.
   52dcg_html([tag(Name,Attrs,Contents)|T]) --> !,
   53  html_element(Name, Attrs, dcg_html(Contents)),
   54  dcg_html(T).
   55% Atom.
   56dcg_html([H|T]) -->
   57  {atom(H)}, !,
   58  atom(H),
   59  dcg_html(T).
   60% Codes list.
   61dcg_html([H|T]) -->
   62  html_string(H), !,
   63  dcg_html(T).
   64% Done.
   65dcg_html([]) --> !, "".
 html_entity(+Name:atom)// is det
   71html_entity(Name) -->
   72  "&",
   73  atom(Name),
   74  ";".
 html_element(+Name:atom)// is det
 html_element(+Name:atom, ?Attributes:list(pair))// is det
   81html_element(Name) -->
   82  html_element(Name, []).
   83
   84
   85html_element(Name, Attrs) -->
   86  "<",
   87  atom(Name),
   88  *(html_attribute, Attrs),
   89  "/>".
 html_element(+Name:atom, ?Attributes:list(pair), :Content_0)// is det
   94html_element(Name0, Attrs, Content_0) -->
   95  "<",
   96  {upcase_atom(Name0, Name)},
   97  atom(Name),
   98  *(html_attribute, Attrs), !,
   99  ">",
  100  Content_0,
  101  "</",
  102  atom(Name),
  103  ">".
 html_graphic(+Code:code)// is det
HTML reserves the following ASCII characters:
  117html_graphic(0'&) --> !, "&amp;".
  118html_graphic(0'') --> !, "&#39".
  119html_graphic(0'") --> !, "&quot;". %"
  120html_graphic(0'<) --> !, "&lt;".
  121html_graphic(0'>) --> !, "&gt;".
  122html_graphic(C)   --> [C].
 html_string(+String:atom)// is det
An HTML string is a sequence of printable or graphic HTML characters. This includes spaces.
  131html_string(S) -->
  132  {atom_codes(S, Cs)},
  133  *(html_graphic, Cs).
 html_style(+Pair:pair)// is det
  139html_style(Name-Value) -->
  140  atom(Name),
  141  ":",
  142  (" ", ! ; ""),
  143  atom(Value),
  144  ";"