35
36:- module(cp_graphviz,
37 [ graphviz_graph//2, 38 reply_graphviz_graph/3 39 ]). 40:- use_module(library(http/http_dispatch)). 41:- use_module(library(http/http_parameters)). 42:- use_module(library(http/http_session)). 43:- use_module(library(http/html_write)). 44:- use_module(library(http/html_head)). 45:- use_module(library(http/http_path)). 46:- use_module(library(process)). 47:- use_module(library(debug)). 48:- use_module(library(option)). 49:- use_module(library(settings)). 50:- use_module(library(semweb/rdf_db)). 51:- use_module(library(semweb/rdf_graphviz)). 52:- use_module(library(http/http_wrapper)). 53
54:- setting(graphviz:format, oneof([svg,canviz]), svg,
55 'Technique to include RDF graphs in a page'). 56
65
66:- html_resource(js('canviz.js'),
67 [ requires([ js('path/path.js'),
68 js('prototype/prototype.js')
69 ])
70 ]). 71:- html_resource(js('path/path.js'),
72 [ requires([ js('prototype/prototype.js')
73 ])
74 ]). 75
78
79:- http_handler(root('graphviz/send_graph'), send_graph, []). 80
110
111:- meta_predicate
112 graphviz_graph(1, :, ?, ?). 113:- dynamic
114 closure/4. 115
116graphviz_graph(_Closure, _:Options) -->
117 { option(render(Renderer), Options, dot),
118 \+ has_graphviz_renderer(Renderer)
119 },
120 !,
121 no_graph_viz(Renderer).
122graphviz_graph(Closure, Options) -->
123 { setting(graphviz:format, DefFormat),
124 Options = _:PlainOptions,
125 option(format(Format), PlainOptions, DefFormat),
126 meta_options(is_meta, Options, QOptions),
127 variant_sha1(Closure+QOptions, Hash),
128 get_time(Now),
129 assert(closure(Hash, Closure, QOptions, Now)),
130 remove_old_closures(Now)
131 },
132 graphviz_graph_fmt(Format, Hash, QOptions).
133
134
135graphviz_graph_fmt(canviz, Hash, _Options) -->
136 !,
137 { http_link_to_id(send_graph, [hash(Hash)], HREF)
138 },
139 html_requires(js('canviz.js')),
140 html([ div(class(graph),
141 div(id(canviz), [])),
142 div(id(debug_output), []),
143 script(type('text/javascript'),
144 \[ 'document.observe(\'dom:loaded\', function() {\n',
145 ' new Canviz(\'canviz\', \'~w\');\n'-[HREF],
146 '});'
147 ])
148 ]).
149graphviz_graph_fmt(svg, Hash, Options) -->
150 { option(object_attributes(Attrs), Options, []),
151 http_link_to_id(send_graph,
152 [ hash(Hash),
153 lang(svg),
154 target('_top')
155 ], HREF)
156 },
157 html([ object([ data(HREF),
158 type('image/svg+xml')
159 | Attrs
160 ],
161 [])
162 ]).
163
164is_meta(wrap_url).
165is_meta(shape_hook).
166is_meta(edge_hook).
167is_meta(bag_shape_hook).
168
169has_graphviz_renderer(Renderer) :-
170 process:exe_options(ExeOptions),
171 absolute_file_name(path(Renderer), _,
172 [ file_errors(fail)
173 | ExeOptions
174 ]).
175
176no_graph_viz(Renderer) -->
177 html(div(id('no-graph-viz'),
178 [ 'The server does not have the graphviz program ',
179 code(Renderer), ' installed in PATH. ',
180 'See ', a(href('http://www.graphviz.org/'),
181 'http://www.graphviz.org/'), ' for details.'
182 ])).
183
189
190send_graph(Request) :-
191 http_parameters(Request,
192 [ hash(Hash,
193 [ description('Hash-key to the graph-data')
194 ]),
195 lang(Lang,
196 [ default(xdot),
197 description('-TXXX option of graphviz')
198 ]),
199 target(Target,
200 [ optional(true),
201 description('Add TARGET= to all links')
202 ])
203 ]),
204 closure(Hash, Closure, Options, _),
205 call(Closure, Graph),
206 reply_graphviz_graph(Graph, Lang, [target(Target)|Options]).
207
208reply_graphviz_graph(_Graph, _Lang, Options) :-
209 option(render(Renderer), Options, dot),
210 \+ has_graphviz_renderer(Renderer),
211 !,
212 http_current_request(Request),
213 http_reply_file(help('error.svg'), [], Request).
214reply_graphviz_graph(Graph, Lang, Options) :-
215 option(target(Target), Options, _),
216 length(Graph, Len),
217 debug(graphviz, 'Graph contains ~D triples', [Len]),
218 select_option(render(Renderer), Options, GraphOptions0, dot),
219 target_option(Target, GraphOptions0, GraphOptions),
220 atom_concat('-T', Lang, GraphLang),
221 process_create(path(Renderer), [GraphLang],
222 [ stdin(pipe(ToDOT)),
223 stdout(pipe(XDotOut)),
224 process(PID)
225 ]),
226 set_stream(ToDOT, encoding(utf8)),
227 set_stream(XDotOut, encoding(utf8)),
228 thread_create(send_to_dot(Graph, GraphOptions, ToDOT), _,
229 [ detached(true) ]),
230 call_cleanup(load_structure(stream(XDotOut),
231 SVGDom0,
232 [ dialect(xml) ]),
233 ( process_wait(PID, _Status),
234 close(XDotOut)
235 )),
236 rewrite_sgv_dom(SVGDom0, SVGDom),
237 graph_mime_type(Lang, ContentType),
238 format('Content-type: ~w~n~n', [ContentType]),
239 xml_write(current_output, SVGDom,
240 [ layout(false)
241 ]).
242
243rewrite_sgv_dom([element(svg, Attrs, Content)],
244 [element(svg, Attrs,
245 [ element(script, ['xlink:href'=SVGPan], []),
246 element(g, [ id=viewport
247 ],
248 Content)
249 ])]) :-
250 http_absolute_location(js('SVGPan.js'), SVGPan, []).
251rewrite_sgv_dom(DOM, DOM).
252
253
254target_option(Target, GraphOptions0, GraphOptions) :-
255 ( nonvar(Target)
256 -> GraphOptions = [target(Target)|GraphOptions0]
257 ; GraphOptions = GraphOptions0
258 ).
259
260
261graph_mime_type(xdot, 'text/plain; charset=UTF-8') :- !.
262graph_mime_type(svg, 'image/svg+xml; charset=UTF-8') :- !.
263graph_mime_type(Lang, 'text/plain; charset=UTF-8') :-
264 print_message(warning,
265 format('Do not know content-type for grapviz \c
266 language ~w. Please extend graph_mime_type/2',
267 Lang)).
268
269send_to_dot(Graph, Options, Out) :-
270 ( debugging(dot)
271 -> retractall(user:graphviz(_,_)),
272 assert(user:graphviz(Graph, Options))
273 ; true
274 ),
275 call_cleanup(gviz_write_rdf(Out, Graph, Options),
276 close(Out)),
277 !.
278
279copy_graph_data(Out) :-
280 debugging(graphviz),
281 !,
282 get_code(Out, C0),
283 copy_graph_data(C0, Out).
284copy_graph_data(Out) :-
285 copy_stream_data(Out, current_output).
286
287copy_graph_data(-1, _) :- !.
288copy_graph_data(C, Stream) :-
289 put_code(C),
290 put_code(user_error, C),
291 get_code(Stream, C2),
292 copy_graph_data(C2, Stream).
293
294
298
299remove_old_closures(Time) :-
300 ( closure(Hash, _, _, Stamp),
301 Time > Stamp+900,
302 retract(closure(Hash, _, _, Stamp)),
303 fail
304 ; true
305 )