Prolog "markup"

Admin User, created Apr 22. 2025
         
/**
* This file provides markup writing predicates.
*
* Warranty & Liability
* To the extent permitted by applicable law and unless explicitly
* otherwise agreed upon, XLOG Technologies AG makes no warranties
* regarding the provided information. XLOG Technologies AG assumes
* no liability that any problems might be solved with the information
* provided by XLOG Technologies AG.
*
* Rights & License
* All industrial property rights regarding the information - copyright
* and patent rights in particular - are the sole property of XLOG
* Technologies AG. If the company was not the originator of some
* excerpts, XLOG Technologies AG has at least obtained the right to
* reproduce, change and translate the information.
*
* Reproduction is restricted to the whole unaltered document. Reproduction
* of the information is only allowed for non-commercial uses. Selling,
* giving away or letting of the execution of the library is prohibited.
* The library can be distributed as part of your applications and libraries
* for execution provided this comment remains unchanged.
*
* Restrictions
* Only to be distributed with programs that add significant and primary
* functionality to the library. Not to be distributed with additional
* software intended to replace any components of the library.
*
* Trademarks
* Jekejeke is a registered trademark of XLOG Technologies AG.
*/
:- ensure_loaded(library(lists)).
:- ensure_loaded(library(util/format)).
:- ensure_loaded(library(util/charsio)).
/*******************************************************************/
/* Tag Output */
/*******************************************************************/
/**
* tag(A):
* tag(W, A):
* The predicate emits the start tag, end tag or self tag A.
* The binary predicate allows specifying a markup writer W.
*/
% tag(+Atom)
tag(A) :-
current_output(W),
tag(W, A).
% tag(+Stream, +Atom)
tag(W, A) :-
ir_object_current(W, 'data', S),
(ir_is_sink(S) ->
(ir_object_current(S, 'data', H), ir_is_element(H) ->
put_atom(S, A);
sys_tag_split(A, L),
maplist(sys_tag_xml(S), L));
sys_tag_split(A, L),
maplist(sys_tag_ascii(W), L)).
/**
* tag_format(T, L):
* tag_format(W, T, L):
* The predicate emits the start tag, end tag or self tag that
* results from formatting the template T with the arguments L.
* The ternary predicate allows specifying a markup writer W.
*/
% tag_format(+Atom, +List)
tag_format(T, L) :-
current_output(W),
tag_format(W, T, L).
% tag_format(+Stream, +Atom, +List)
tag_format(W, T, L) :-
format_atom(T, L, A),
tag(W, A).
/*******************************************************************/
/* XML Mapping */
/*******************************************************************/
% sys_tag_xml(+Stream, +Atom)
sys_tag_xml(S, A) :-
sub_atom(A, 0, _, _, '</'), !,
sys_tag_name(A, Y),
(markup_display(Y, D) -> true; D = other),
(D = inline -> put_atom(S, A);
D = block -> put_atom(S, A), put_atom(S, '\n');
sys_indent_dec(S),
sys_indent_tab(S), put_atom(S, A), put_atom(S, '\n')).
sys_tag_xml(S, A) :-
sub_atom(A, _, _, 0, '/>'), !,
sys_tag_name(A, Y),
(markup_display(Y, D) -> true; D = other),
(D = inline -> put_atom(S, A);
D = block -> put_atom(S, A), put_atom(S, '\n'), sys_indent_tab(S);
sys_indent_tab(S), put_atom(S, A), put_atom(S, '\n')).
sys_tag_xml(S, A) :-
sub_atom(A, 0, _, _, '<'), !,
sys_tag_name(A, Y),
(markup_display(Y, D) -> true; D = other),
(D = inline -> put_atom(S, A);
D = block -> sys_indent_tab(S), put_atom(S, A);
sys_indent_tab(S), put_atom(S, A), put_atom(S, '\n'),
sys_indent_inc(S)).
sys_tag_xml(S, A) :-
put_atom(S, A).
:- multifile markup_display/2.
markup_display('p', block).
markup_display('div', block).
markup_display('title', block).
markup_display('h1', block).
markup_display('h2', block).
markup_display('h3', block).
markup_display('th', block).
markup_display('td', block).
markup_display('br', block).
markup_display('li', block).
markup_display('dt', block).
markup_display('dd', block).
markup_display('i', inline).
markup_display('u', inline).
markup_display('span', inline).
markup_display('b', inline).
markup_display('a', inline).
/*******************************************************************/
/* Ansi Mapping */
/*******************************************************************/
% sys_tag_ascii(+Stream, +Atom)
sys_tag_ascii(W, A) :-
sub_atom(A, 0, _, _, '</'), !,
sys_tag_name(A, Y),
(ansi_end(Y, C) -> true; C = ''),
(markup_display(Y, D) -> true; D = other),
(D = inline -> put_atom(W, C);
D = block -> put_atom(W, C), put_atom(W, '\n');
sys_indent_dec(W)).
sys_tag_ascii(W, A) :-
sub_atom(A, _, _, 0, '/>'), !,
sys_tag_name(A, Y),
(markup_display(Y, D) -> true; D = other),
(D = block -> put_atom(W, '\n'); true).
sys_tag_ascii(W, A) :-
sub_atom(A, 0, _, _, '<'), !,
sys_tag_name(A, Y),
(ansi_begin(Y, A, C) -> true; C = ''),
(markup_display(Y, D) -> true; D = other),
(D = inline -> put_atom(W, C);
D = block -> sys_indent_dec(W), sys_indent_tab(W),
sys_indent_inc(W), put_atom(W, C);
sys_indent_inc(W)).
sys_tag_ascii(W, A) :-
xml_escape(B, A),
put_atom(W, B).
% ansi_begin(+Atom, +Atom, -Atom)
ansi_begin(li, '<li>', ' - ').
ansi_begin(dd, '<dd>', ' ').
ansi_begin(i, '<i>', '\x1B\[3m').
ansi_begin(u, '<u>', '\x1B\[4m').
ansi_begin(span, Tag, Esc) :-
sub_atom(Tag, 0, Len, _, '<span style="color: '),
sub_atom(Tag, _, Len2, 0, '">'),
sub_atom(Tag, Len, _, Len2, Color),
ansi_color(Color, Char),
atom_join(['\x1B\[3', Char, 'm'], Esc).
ansi_begin(a, Tag, Esc) :-
sub_atom(Tag, 0, Len, _, '<a href="'),
sub_atom(Tag, _, Len2, 0, '">'),
sub_atom(Tag, Len, _, Len2, Link),
atom_join(['\x1B\]8;;', Link, '\x1B\\\'], Esc).
% ansi_end(+Atom, -Atom)
ansi_end(dt, ':').
ansi_end(i, '\x1B\[23m').
ansi_end(u, '\x1B\[24m').
ansi_end(span, '\x1B\[39m').
ansi_end(a, '\x1B\]8;;\x1B\\\').
% ansi_color(+Atom, -Atom)
ansi_color('black', '0').
ansi_color('red', '1').
ansi_color('green', '2').
ansi_color('yellow', '3').
ansi_color('blue', '4').
ansi_color('magenta', '5').
ansi_color('cyan', '6').
ansi_color('white', '7').
/*******************************************************************/
/* Tag Split */
/*******************************************************************/
% sys_tag_split(+Atom, -List)
sys_tag_split(A, R) :-
atom_codes(A, L),
sys_tag_mix(R, L, []).
% sys_tag_mix(+List, -List)
sys_tag_mix([A|R]) --> [0'<], !,
sys_tag_tag(F),
{atom_codes(A, [0'<|F])},
sys_tag_mix(R).
sys_tag_mix([A|R]) --> [X], !,
sys_tag_text(F),
{atom_codes(A, [X|F])},
sys_tag_mix(R).
sys_tag_mix([]) --> [].
% sys_tag_tag(-List, +Stream, +List, -List)
sys_tag_tag([0'>]) --> [0'>], !.
sys_tag_tag([X|F]) --> [X], !,
sys_tag_tag(F).
sys_tag_tag(_) -->
{throw(error(syntax_error(missing_angle),_))}.
% sys_tag_text(-List, +List, -List)
sys_tag_text([X|F]) --> [X], {X \== 0'<}, !,
sys_tag_text(F).
sys_tag_text([]) --> [].
/*******************************************************************/
/* Tag Name */
/*******************************************************************/
% sys_tag_name(+Atom, -Atom)
sys_tag_name(A, Y) :-
sub_atom(A, Pos, _, _, ' '), !,
sys_tag_left(A, Left),
Len is Pos-Left,
sub_atom(A, Left, Len, _, Y).
sys_tag_name(A, Y) :-
sys_tag_left(A, Left),
sys_tag_right(A, Right),
sub_atom(A, Left, _, Right, Y).
% sys_tag_left(+Atom, -Integer)
sys_tag_left(A, 2) :-
sub_atom(A, 0, _, _, '</'), !.
sys_tag_left(_, 1).
% sys_tag_right(+Atom, -Integer)
sys_tag_right(A, 2) :-
sub_atom(A, _, _, 0, '/>'), !.
sys_tag_right(_, 1).
/*******************************************************************/
/* DOM Indentation */
/*******************************************************************/
% sys_indent_tab(+Stream)
sys_indent_tab(S) :-
ir_object_current(S, 'indent', I),
tab(S, I).
% sys_indent_inc(+Stream)
sys_indent_inc(S) :-
ir_object_current(S, 'indent', I),
I2 is I+3,
ir_object_set(S, 'indent', I2).
% sys_indent_dec(+Stream)
sys_indent_dec(S) :-
ir_object_current(S, 'indent', I),
I2 is I-3,
ir_object_set(S, 'indent', I2).
/*******************************************************************/
/* DOM Access */
/*******************************************************************/
/**
* dom_output_new(W):
* The predicate succeeds in W with a new writer to the cursor.
* The binary predicate allows specifying an underlying stream S.
*/
% dom_output_new(-Stream)
dom_output_new(Stream) :-
dom_cell_current(Elem),
dom_output_new(Elem, Stream).
/**
* dom_error_new(S, W):
* The predicate succeeds in W with a new writer to the cursor.
* The binary predicate allows specifying an underlying stream S.
*/
% dom_error_new(-Stream)
dom_error_new(Stream) :-
dom_cell_current(Elem),
dom_error_new(Elem, Stream).
/**
* The predicate succeeds in C with the cursor.
*/
% dom_cell_current(-Element)
dom_cell_current(Elem) :-
current_output(Stream),
flush_output(Stream),
ir_object_current(Stream, 'data', H),
ir_object_current(H, 'data', Elem).
/**
* The predicate succeeds. As side effect the cursor changes to C.
*/
% dom_cell_set(-Element)
dom_cell_set(Elem) :-
current_output(Stream),
ir_object_current(Stream, 'data', H),
ir_object_set(H, 'data', Elem).
/*******************************************************************/
/* Report Support */
/*******************************************************************/
% sys_html_header(+Stream, +Term)
sys_html_header(S, v(I,A,B,C)) :-
tag(S, '<html author="7">'),
tag(S, '<head>'),
tag_format(S, '<link rel="raw" title="Document" href="~a"/>', [C]),
tag(S, '<meta http-equiv="Content-Type" content="text/html; charset=UTF-8"/>'),
tag(S, '<title editable="nocomment">'), put_atom(S, A), tag(S, '</title>'),
tag(S, '<link href="style.css" rel="stylesheet" type="text/css"/>'),
tag(S, '</head>'),
tag(S, '<body class="showbody">'),
atom_time(D, '%Y-%m-%d %H:%M:%S', I),
tag_format(S, '<h1 date="~a">', [D]), put_atom(S, B), tag(S, '</h1>').
sys_html_header(S, v(A,B)) :-
tag(S, '<html>'),
tag(S, '<head>'),
tag(S, '<meta http-equiv="Content-Type" content="text/html; charset=UTF-8"/>'),
tag(S, '<title editable="nocomment">'), put_atom(S, A), tag(S, '</title>'),
tag(S, '<link href="style.css" rel="stylesheet" type="text/css"/>'),
tag(S, '</head>'),
tag(S, '<body class="showbody">'),
tag(S, '<h1>'), put_atom(S, B), tag(S, '</h1>').
% sys_html_footer(+Stream)
sys_html_footer(S) :-
tag(S, '</body>'),
tag(S, '</html>').
/*******************************************************************/
/* Decode Page Options */
/*******************************************************************/
% sys_page_opts(+List, +Pair, -Pair)
sys_page_opts(V, _, _) :- var(V),
throw(error(instantiation_error,_)).
sys_page_opts([X|L], I, O) :- !,
sys_page_opt(X, I, H),
sys_page_opts(L, H, O).
sys_page_opts([], H, H) :- !.
sys_page_opts(L, _, _) :-
throw(error(type_error(list,L),_)).
% sys_page_opt(+Option, +Pair, -Pair)
sys_page_opt(V, _, _) :- var(V),
throw(error(instantiation_error,_)).
sys_page_opt(title(A), v(_,Y), v(A,Y)) :- !.
sys_page_opt(header(A), v(X,_), v(X,A)) :- !.
sys_page_opt(O, _, _) :-
throw(error(type_error(page_option,O),_)).
/*******************************************************************/
/* Foreign Predicates */
/*******************************************************************/
% ir_is_sink(O):
% defined in foreign(misc/domlib)
% ir_is_element(O):
% defined in foreign(misc/domlib)
% dom_output_new(S, W):
% defined in foreign(misc/domlib)
% dom_error_new(S, W):
% defined in foreign(misc/domlib)
:- ensure_loaded(foreign(misc/domlib)).
/****************************************************************/
/* Error Texts */
/****************************************************************/
% strings(+Atom, +Atom, -Atom)
:- multifile strings/3.
strings('syntax_error.missing_angle', de, 'Kein XML Tag.').
strings('syntax_error.missing_angle', '', 'Not a XML tag.').