29
30:- module(swish_render_lpad,
31 [ term_rendering//3 32 ,clauses//1
33 ]). 34:- use_module(library(apply)). 35:- use_module(library(lists)). 36:- use_module(library(option)). 37:- use_module(library(http/html_write)). 38:- use_module(library(http/term_html)). 39:- use_module(library(slipcover)). 40:- use_module('../render'). 41
42:- register_renderer(lpad, "Render a logic program with annotated disjunctions").
59term_rendering(Term, _Vars, _Options) -->
60 {is_list_of_clauses(Term)
61 }, !,
62 html(pre(\clauses(Term))).
63
64clauses([]) --> [].
65clauses([HC|T]) -->
66 {
67 numbervars(HC,0,_),
68 HC=(H:-B),!,
69 list2or(HL,H),
70 list2and(BL,B)
71 },
72 disj_clause(HL,BL),
73 clauses(T).
74
75disj_clause(H,B)-->
76 {format(atom(I),' :-~n',[])},
77 head(H,B,I).
78
79head([H:1.0|_Rest],[],_I)-->
80 {format(atom(A),"~q.~n~n",[H])},!,
81 [A].
82
83head([H:1.0|_Rest],B,I)-->
84 {format(atom(A),"~q",[H])},!,
85 [A,I],
86 body(B).
87
88head([H:P,'':_P],[],_I)-->
89 {format(atom(A),"~q:~g.~n~n",[H,P])},!,
90 [A].
91
92head([H:P,'':_P],B,I)-->
93 {format(atom(A),"~q:~g",[H,P])},!,
94 [A,I],
95 body(B).
96
97
98head([H:P],true,_I)-->
99 {format(atom(A),"~q:~g.~n~n",[H,P])},!,
100 [A].
101
102head([H:P],B,I)-->
103 {format(atom(A),"~q:~g",[H,P])},!,
104 [A,I],
105 body(B).
106
107head([H:P|Rest],B,I)-->
108 {format(atom(A),"~q:~g ; ",[H,P])},!,
109 [A],
110 head(Rest,B,I).
111
112head([H],[],_I)-->
113 {format(atom(A),"~q.~n~n",[H])},!,
114 [A].
115
116head([H],B,I)-->
117 {format(atom(A),"~q",[H])},
118 [A,I],
119 body(B).
120
121body([])-->
122 {format(atom(A)," true.~n~n",[])},
123 [A].
124
125body([H])-->
126 {format(atom(A)," ~q.~n~n",[H])},!,
127 [A].
128
129body([H|T])-->
130 {format(atom(A)," ~q,~n",[H])},
131 [A],body(T).
143is_list_of_clauses(Term) :-
144 is_list(Term), Term \== [],
145 maplist(is_clause, Term).
146
147is_clause((_H :- _B)).
153is_list_of_lists(Term, Rows, Cols) :-
154 is_list(Term), Term \== [],
155 length(Term, Rows),
156 maplist(is_list_row(Cols), Term),
157 Cols > 0.
158
159is_list_row(Length, Term) :-
160 is_list(Term),
161 length(Term, Length)
SWISH table renderer
Render table-like data. */