35
36:- module(swish_html_output,
37 [ html/1, 38 html//1, 39 html/4, 40 safe_raw_html/1 41 ]). 42:- use_module(library(http/html_write), except([html//1])). 43:- use_module(library(pengines)). 44:- use_module(library(sandbox)). 45:- use_module(library(lists)). 46:- use_module(library(error)).
55:- html_meta
56 html(html),
57 html(html,?,?).
66html(Spec) :-
67 pengine_self(_),
68 !,
69 make_safe_html(Spec, SafeSpec),
70 pengines_io:send_html(SafeSpec).
71html(Spec) :-
72 phrase(html(Spec), Tokens),
73 with_output_to(
74 string(HTML),
75 print_html(current_output, Tokens)),
76 format('~w', [HTML]).
82html(Spec) -->
83 { make_safe_html(Spec, SafeSpec) },
84 html_write:html(SafeSpec).
85
86make_safe_html(HTML0, HTML) :-
87 ( pengine_self(M)
88 -> true
89 ; prolog_load_context(module, M)
90 ),
91 make_safe_html(HTML0, M, HTML).
92
93make_safe_html(Var, M, M:html(Var)) :-
94 var(Var),
95 !.
96make_safe_html(Module:HTML0, M, Module:HTML) :-
97 !,
98 ( Module == M
99 -> true
100 ; permission_error(cross_module_call, M, Module:HTML)
101 ),
102 make_safe_html(HTML0, M, HTML).
103make_safe_html([], _, []) :-
104 !.
105make_safe_html([H0|T0], M, [H|T]) :-
106 !,
107 make_safe_html(H0, M, H),
108 make_safe_html(T0, M, T).
109make_safe_html(element(Name, Attrs0, Content0), M,
110 element(Name, Attrs, Content)) :-
111 !,
112 must_be(atom, Name),
113 safe_attrs(Attrs0, M, Attrs),
114 make_safe_html(Content0, M, Content).
115make_safe_html(Format-Args, _M, Format-Args) :-
116 !,
117 safe_goal(format(Format, Args)).
118make_safe_html(\Raw0, M, \Raw) :-
119 is_list(Raw0),
120 !,
121 make_safe_raw(Raw0, M, Raw).
122make_safe_html(\Goal, M, \Goal) :-
123 !,
124 must_be(callable, Goal),
125 dcg_extend(Goal, DcgGoal),
126 safe_goal(M:DcgGoal).
127make_safe_html(Elem0, M, Elem) :-
128 Elem0 =.. [Name, Attrs0, Content0],
129 !,
130 safe_attrs(Attrs0, M, Attrs),
131 make_safe_html(Content0, M, Content),
132 Elem =.. [Name, Attrs, Content].
133make_safe_html(Elem0, M, Elem) :-
134 Elem0 =.. [Name, AttrsOrContent0],
135 !,
136 ( html_write:layout(Name, _, empty)
137 -> safe_attrs(AttrsOrContent0, M, Safe)
138 ; make_safe_html(AttrsOrContent0, M, Safe)
139 ),
140 Elem =.. [Name, Safe].
141make_safe_html(Text, _, Text) :-
142 atomic(Text),
143 !.
144make_safe_html(Term, _, _) :-
145 domain_error(html_term, Term).
146
147safe_attrs([], _, []) :-
148 !.
149safe_attrs([H0|T0], M, [H|T]) :-
150 !,
151 safe_attrs(H0, M, H),
152 safe_attrs(T0, M, T).
153safe_attrs(Name=Value0, M, Name=Value) :-
154 !,
155 safe_attr_value(Value0, M, Value).
156safe_attrs(NameValue0, M, NameValue) :-
157 !,
158 NameValue0 =.. [Name,Value0],
159 safe_attr_value(M, Value0, Value),
160 NameValue =.. [Name,Value].
161
162safe_attr_value(_, Value0, _) :-
163 var(Value0),
164 !,
165 instantiation_error(Value0).
166safe_attr_value(M, Value0, Value) :-
167 is_list(Value0),
168 !,
169 maplist(safe_attr_value(M), Value0, Value).
170safe_attr_value(_M, Format-Args, Format-Args) :-
171 !,
172 safe_goal(format(Format, Args)).
173safe_attr_value(M, A0+B0, A+B) :-
174 safe_attr_value(M, A0, A),
175 safe_attr_value(M, B0, B).
176safe_attr_value(_, V, V) :-
177 atomic(V).
183make_safe_raw(Raw0, _M, \safe_raw_html(Raw0)) :-
184 var(Raw0),
185 !.
186make_safe_raw([], _, []) :-
187 !.
188make_safe_raw([H0|T0], M, [H|T]) :-
189 !,
190 make_safe_raw(H0, M, H),
191 make_safe_raw(T0, M, T).
192make_safe_raw(Format-Args, _, Format-Args) :-
193 !,
194 safe_goal(format(Format, Args)).
195make_safe_raw(Atomic, _, Atomic) :-
196 atomic(Atomic),
197 !.
198make_safe_raw(\Goal, M, \Goal) :-
199 !,
200 must_be(callable, Goal),
201 dcg_extend(Goal, DcgGoal),
202 safe_goal(M:DcgGoal).
203make_safe_raw(Term, _, _) :-
204 domain_error(html_raw, Term).
210safe_raw_html(Raw0) :-
211 ( pengine_self(M)
212 -> true
213 ; prolog_load_context(module, M)
214 ),
215 make_safe_raw(Raw0, M, Raw),
216 html(\[Raw]).
217
218dcg_extend(Goal, DcgGoal) :-
219 must_be(callable, Goal),
220 Goal \= (_:_),
221 Goal =.. List,
222 append(List, [_,_], ExList),
223 DcgGoal =.. ExList.
224
225:- multifile sandbox:safe_primitive/1. 226
227sandbox:safe_meta_predicate(swish_html_output:html/1).
228sandbox:safe_meta_predicate(swish_html_output:html/3).
229sandbox:safe_meta_predicate(swish_html_output:safe_raw_html/1)
SWISH HTML Output
This module provides the predicate html/1 that allows for inserting HTML into the SWISH output window as well as for evaluable cells in markdown cells of notebooks. */