1:- encoding(utf8).
2:- module(
3 dot_html,
4 [
5 dot_html//1 6 ]
7).
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)).
48dot_html(b(Spec)) --> !,
49 html_element(b, [], dot_html:dot_html(Spec)).
52dot_html(br) --> !,
53 dot_html(br([])).
54dot_html(br(Attrs0)) --> !,
55 {attributes_(Attrs0, Attrs)},
56 html_element(br, Attrs, "").
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)).
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)).
102dot_html(i(Spec)) --> !,
103 html_element(i, [], dot_html:dot_html(Spec)).
107dot_html(img(Attrs0)) --> !,
108 {attributes_(Attrs0, Attrs)},
109 html_element(img, Attrs).
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_([])) --> !, "".
128dot_html(s(Spec)) --> !,
129 html_element(s, [], dot_html:dot_html(Spec)).
131dot_html(sub(Spec)) --> !,
132 html_element(sub, [], dot_html:dot_html(Spec)).
134dot_html(sup(Spec)) --> !,
135 html_element(sup, [], dot_html:dot_html(Spec)).
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))).
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).
176dot_html(Spec) -->
177 syntax_error(dot_html_like_label(Spec)).
178
179attributes_(Attrs, Attrs) :-
180 is_list(Attrs), !.
181attributes_(Attr, [Attr])
DOT HTML-like labels
Grammar taken from the GraphViz Web site:
*/