35
36:- module(pldoc_http,
37 [ doc_enable/1, 38 doc_server/1, 39 doc_server/2, 40 doc_browser/0,
41 doc_browser/1 42 ]). 43:- use_module(library(pldoc)). 44:- use_module(library(http/thread_httpd)). 45:- use_module(library(http/http_parameters)). 46:- use_module(library(http/html_write)). 47:- use_module(library(http/mimetype)). 48:- use_module(library(dcg/basics)). 49:- use_module(library(http/http_dispatch)). 50:- use_module(library(http/http_hook)). 51:- use_module(library(http/http_path)). 52:- use_module(library(http/http_wrapper)). 53:- use_module(library(uri)). 54:- use_module(library(debug)). 55:- use_module(library(lists)). 56:- use_module(library(url)). 57:- use_module(library(socket)). 58:- use_module(library(option)). 59:- use_module(library(error)). 60:- use_module(library(www_browser)). 61:- use_module(pldoc(doc_process)). 62:- use_module(pldoc(doc_htmlsrc)). 63:- use_module(pldoc(doc_html)). 64:- use_module(pldoc(doc_index)). 65:- use_module(pldoc(doc_search)). 66:- use_module(pldoc(doc_man)). 67:- use_module(pldoc(doc_wiki)). 68:- use_module(pldoc(doc_util)). 69:- use_module(pldoc(doc_access)). 70:- use_module(pldoc(doc_pack)). 71:- use_module(pldoc(man_index)). 72
79
80:- dynamic
81 doc_server_port/1,
82 doc_enabled/0. 83
84http:location(pldoc, root(pldoc), []).
85http:location(pldoc_man, pldoc(refman), []).
86http:location(pldoc_pkg, pldoc(package), []).
87http:location(pldoc_resource, Path, []) :-
88 http_location_by_id(pldoc_resource, Path).
89
95
96doc_enable(true) :-
97 ( doc_enabled
98 -> true
99 ; assertz(doc_enabled)
100 ).
101doc_enable(false) :-
102 retractall(doc_enabled).
103
137
138doc_server(Port) :-
139 doc_server(Port,
140 [ allow(localhost),
141 allow(ip(127,0,0,1)) 142 ]).
143
144doc_server(Port, _) :-
145 doc_enable(true),
146 catch(doc_current_server(Port), _, fail),
147 !.
148doc_server(Port, Options) :-
149 doc_enable(true),
150 prepare_editor,
151 host_access_options(Options, ServerOptions),
152 http_absolute_location(pldoc('.'), Entry, []),
153 merge_options(ServerOptions,
154 [ port(Port),
155 entry_page(Entry)
156 ], HTTPOptions),
157 http_server(http_dispatch, HTTPOptions),
158 assertz(doc_server_port(Port)).
159
170
171doc_current_server(Port) :-
172 ( doc_server_port(P)
173 -> Port = P
174 ; http_current_server(_:_, P)
175 -> Port = P
176 ; existence_error(http_server, pldoc)
177 ).
178
183
184doc_browser :-
185 doc_browser([]).
186doc_browser(Spec) :-
187 catch(doc_current_server(Port),
188 error(existence_error(http_server, pldoc), _),
189 doc_server(Port)),
190 browser_url(Spec, Request),
191 format(string(URL), 'http://localhost:~w~w', [Port, Request]),
192 www_open_url(URL).
193
194browser_url([], Root) :-
195 !,
196 http_location_by_id(pldoc_root, Root).
197browser_url(Name, URL) :-
198 atom(Name),
199 !,
200 browser_url(Name/_, URL).
201browser_url(Name//Arity, URL) :-
202 must_be(atom, Name),
203 integer(Arity),
204 !,
205 PredArity is Arity+2,
206 browser_url(Name/PredArity, URL).
207browser_url(Name/Arity, URL) :-
208 !,
209 must_be(atom, Name),
210 ( man_object_property(Name/Arity, summary(_))
211 -> format(string(S), '~q/~w', [Name, Arity]),
212 http_link_to_id(pldoc_man, [predicate=S], URL)
213 ; browser_url(_:Name/Arity, URL)
214 ).
215browser_url(Spec, URL) :-
216 !,
217 Spec = M:Name/Arity,
218 doc_comment(Spec, _Pos, _Summary, _Comment),
219 !,
220 ( var(M)
221 -> format(string(S), '~q/~w', [Name, Arity])
222 ; format(string(S), '~q:~q/~w', [M, Name, Arity])
223 ),
224 http_link_to_id(pldoc_object, [object=S], URL).
225
230
231prepare_editor :-
232 current_prolog_flag(editor, pce_emacs),
233 !,
234 start_emacs.
235prepare_editor.
236
237
238 241
242:- http_handler(pldoc(.), pldoc_root,
243 [ prefix,
244 authentication(pldoc(read)),
245 condition(doc_enabled)
246 ]). 247:- http_handler(pldoc('index.html'), pldoc_index, []). 248:- http_handler(pldoc(file), pldoc_file, []). 249:- http_handler(pldoc(place), go_place, []). 250:- http_handler(pldoc(edit), pldoc_edit,
251 [authentication(pldoc(edit))]). 252:- http_handler(pldoc(doc), pldoc_doc, [prefix]). 253:- http_handler(pldoc(man), pldoc_man, []). 254:- http_handler(pldoc(doc_for), pldoc_object, [id(pldoc_doc_for)]). 255:- http_handler(pldoc(search), pldoc_search, []). 256:- http_handler(pldoc('res/'), pldoc_resource, [prefix]). 257
258
265
266pldoc_root(Request) :-
267 http_parameters(Request,
268 [ empty(Empty, [ oneof([true,false]),
269 default(false)
270 ])
271 ]),
272 pldoc_root(Request, Empty).
273
274pldoc_root(Request, false) :-
275 http_location_by_id(pldoc_root, Root),
276 memberchk(path(Path), Request),
277 Root \== Path,
278 !,
279 existence_error(http_location, Path).
280pldoc_root(_Request, false) :-
281 working_directory(Dir0, Dir0),
282 allowed_directory(Dir0),
283 !,
284 ensure_slash_end(Dir0, Dir1),
285 doc_file_href(Dir1, Ref0),
286 atom_concat(Ref0, 'index.html', Index),
287 throw(http_reply(see_other(Index))).
288pldoc_root(Request, _) :-
289 pldoc_index(Request).
290
291
296
297pldoc_index(_Request) :-
298 reply_html_page(pldoc(index),
299 title('SWI-Prolog documentation'),
300 [ \doc_links('', []),
301 h1('SWI-Prolog documentation'),
302 \man_overview([])
303 ]).
304
305
309
310pldoc_file(Request) :-
311 http_parameters(Request,
312 [ file(File, [])
313 ]),
314 ( source_file(File)
315 -> true
316 ; throw(http_reply(forbidden(File)))
317 ),
318 doc_for_file(File, []).
319
327
328pldoc_edit(Request) :-
329 http:authenticate(pldoc(edit), Request, _),
330 http_parameters(Request,
331 [ file(File,
332 [ optional(true),
333 description('Name of the file to edit')
334 ]),
335 line(Line,
336 [ optional(true),
337 integer,
338 description('Line in the file')
339 ]),
340 name(Name,
341 [ optional(true),
342 description('Name of a Prolog predicate to edit')
343 ]),
344 arity(Arity,
345 [ integer,
346 optional(true),
347 description('Arity of a Prolog predicate to edit')
348 ]),
349 module(Module,
350 [ optional(true),
351 description('Name of a Prolog module to search for predicate')
352 ])
353 ]),
354 ( atom(File)
355 -> allowed_file(File)
356 ; true
357 ),
358 ( atom(File), integer(Line)
359 -> Edit = file(File, line(Line))
360 ; atom(File)
361 -> Edit = file(File)
362 ; atom(Name), integer(Arity)
363 -> ( atom(Module)
364 -> Edit = (Module:Name/Arity)
365 ; Edit = (Name/Arity)
366 )
367 ),
368 edit(Edit),
369 format('Content-type: text/plain~n~n'),
370 format('Started ~q~n', [edit(Edit)]).
371pldoc_edit(_Request) :-
372 http_location_by_id(pldoc_edit, Location),
373 throw(http_reply(forbidden(Location))).
374
375
379
380go_place(Request) :-
381 http_parameters(Request,
382 [ place(Place, [])
383 ]),
384 places(Place).
385
386places(':packs:') :-
387 !,
388 http_link_to_id(pldoc_pack, [], HREF),
389 throw(http_reply(moved(HREF))).
390places(Dir0) :-
391 expand_alias(Dir0, Dir),
392 ( allowed_directory(Dir)
393 -> format(string(IndexFile), '~w/index.html', [Dir]),
394 doc_file_href(IndexFile, HREF),
395 throw(http_reply(moved(HREF)))
396 ; throw(http_reply(forbidden(Dir)))
397 ).
398
399
403
404allowed_directory(Dir) :-
405 source_directory(Dir),
406 !.
407allowed_directory(Dir) :-
408 working_directory(CWD, CWD),
409 same_file(CWD, Dir).
410allowed_directory(Dir) :-
411 prolog:doc_directory(Dir).
412
413
418
419allowed_file(File) :-
420 source_file(_, File),
421 !.
422allowed_file(File) :-
423 absolute_file_name(File, Canonical),
424 file_directory_name(Canonical, Dir),
425 allowed_directory(Dir).
426
427
431
432pldoc_resource(Request) :-
433 http_location_by_id(pldoc_resource, ResRoot),
434 memberchk(path(Path), Request),
435 atom_concat(ResRoot, File, Path),
436 file(File, Local),
437 http_reply_file(pldoc(Local), [], Request).
438
439file('pldoc.css', 'pldoc.css').
440file('pllisting.css', 'pllisting.css').
441file('pldoc.js', 'pldoc.js').
442file('edit.png', 'edit.png').
443file('editpred.png', 'editpred.png').
444file('up.gif', 'up.gif').
445file('source.png', 'source.png').
446file('public.png', 'public.png').
447file('private.png', 'private.png').
448file('reload.png', 'reload.png').
449file('favicon.ico', 'favicon.ico').
450file('h1-bg.png', 'h1-bg.png').
451file('h2-bg.png', 'h2-bg.png').
452file('pub-bg.png', 'pub-bg.png').
453file('priv-bg.png', 'priv-bg.png').
454file('multi-bg.png', 'multi-bg.png').
455
456
467
468pldoc_doc(Request) :-
469 memberchk(path(ReqPath), Request),
470 http_location_by_id(pldoc_doc, Me),
471 atom_concat(Me, AbsFile0, ReqPath),
472 ( sub_atom(ReqPath, _, _, 0, /)
473 -> atom_concat(ReqPath, 'index.html', File),
474 throw(http_reply(moved(File)))
475 ; clean_path(AbsFile0, AbsFile1),
476 expand_alias(AbsFile1, AbsFile),
477 is_absolute_file_name(AbsFile)
478 -> documentation(AbsFile, Request)
479 ).
480
481documentation(Path, Request) :-
482 file_base_name(Path, Base),
483 file(_, Base), 484 !,
485 http_reply_file(pldoc(Base), [], Request).
486documentation(Path, Request) :-
487 file_name_extension(_, Ext, Path),
488 autolink_extension(Ext, image),
489 http_reply_file(Path, [unsafe(true)], Request).
490documentation(Path, Request) :-
491 Index = '/index.html',
492 sub_atom(Path, _, _, 0, Index),
493 atom_concat(Dir, Index, Path),
494 exists_directory(Dir), 495 !,
496 ( allowed_directory(Dir)
497 -> edit_options(Request, EditOptions),
498 doc_for_dir(Dir, EditOptions)
499 ; throw(http_reply(forbidden(Dir)))
500 ).
501documentation(File, Request) :-
502 wiki_file(File, WikiFile),
503 !,
504 ( allowed_file(WikiFile)
505 -> true
506 ; throw(http_reply(forbidden(File)))
507 ),
508 edit_options(Request, Options),
509 doc_for_wiki_file(WikiFile, Options).
510documentation(Path, Request) :-
511 pl_file(Path, File),
512 !,
513 ( allowed_file(File)
514 -> true
515 ; throw(http_reply(forbidden(File)))
516 ),
517 doc_reply_file(File, Request).
518documentation(Path, _) :-
519 throw(http_reply(not_found(Path))).
520
521:- public
522 doc_reply_file/2. 523
524doc_reply_file(File, Request) :-
525 http_parameters(Request,
526 [ public_only(Public),
527 reload(Reload),
528 show(Show),
529 format_comments(FormatComments)
530 ],
531 [ attribute_declarations(param)
532 ]),
533 ( exists_file(File)
534 -> true
535 ; throw(http_reply(not_found(File)))
536 ),
537 ( Reload == true,
538 source_file(File)
539 -> load_files(File, [if(changed), imports([])])
540 ; true
541 ),
542 edit_options(Request, EditOptions),
543 ( Show == src
544 -> format('Content-type: text/html~n~n', []),
545 source_to_html(File, stream(current_output),
546 [ skin(src_skin(Request, Show, FormatComments)),
547 format_comments(FormatComments)
548 ])
549 ; Show == raw
550 -> http_reply_file(File,
551 [ unsafe(true), 552 mime_type(text/plain)
553 ], Request)
554 ; doc_for_file(File,
555 [ public_only(Public),
556 source_link(true)
557 | EditOptions
558 ])
559 ).
560
561
562:- public src_skin/5. 563
564src_skin(Request, _Show, FormatComments, header, Out) :-
565 memberchk(request_uri(ReqURI), Request),
566 negate(FormatComments, AltFormatComments),
567 replace_parameters(ReqURI, [show(raw)], RawLink),
568 replace_parameters(ReqURI, [format_comments(AltFormatComments)], CmtLink),
569 phrase(html(div(class(src_formats),
570 [ 'View source with ',
571 a(href(CmtLink), \alt_view(AltFormatComments)),
572 ' or as ',
573 a(href(RawLink), raw)
574 ])), Tokens),
575 print_html(Out, Tokens).
576
577alt_view(true) -->
578 html('formatted comments').
579alt_view(false) -->
580 html('raw comments').
581
582negate(true, false).
583negate(false, true).
584
585replace_parameters(ReqURI, Extra, URI) :-
586 uri_components(ReqURI, C0),
587 uri_data(search, C0, Search0),
588 ( var(Search0)
589 -> uri_query_components(Search, Extra)
590 ; uri_query_components(Search0, Form0),
591 merge_options(Extra, Form0, Form),
592 uri_query_components(Search, Form)
593 ),
594 uri_data(search, C0, Search, C),
595 uri_components(URI, C).
596
597
602
603edit_options(Request, [edit(true)]) :-
604 catch(http:authenticate(pldoc(edit), Request, _), _, fail),
605 !.
606edit_options(_, []).
607
608
610
611pl_file(File, PlFile) :-
612 file_name_extension(Base, html, File),
613 !,
614 absolute_file_name(Base,
615 PlFile,
616 [ file_errors(fail),
617 file_type(prolog),
618 access(read)
619 ]).
620pl_file(File, File).
621
626
627wiki_file(File, TxtFile) :-
628 file_name_extension(_, Ext, File),
629 wiki_file_extension(Ext),
630 !,
631 TxtFile = File.
632wiki_file(File, TxtFile) :-
633 file_base_name(File, Base),
634 autolink_file(Base, wiki),
635 !,
636 TxtFile = File.
637wiki_file(File, TxtFile) :-
638 file_name_extension(Base, html, File),
639 wiki_file_extension(Ext),
640 file_name_extension(Base, Ext, TxtFile),
641 access_file(TxtFile, read).
642
643wiki_file_extension(md).
644wiki_file_extension(txt).
645
646
650
651clean_path(Path0, Path) :-
652 current_prolog_flag(windows, true),
653 sub_atom(Path0, 2, _, _, :),
654 !,
655 sub_atom(Path0, 1, _, 0, Path).
656clean_path(Path, Path).
657
658
669
670pldoc_man(Request) :-
671 http_parameters(Request,
672 [ predicate(PI, [optional(true)]),
673 function(Fun, [optional(true)]),
674 'CAPI'(F, [optional(true)]),
675 section(Sec, [optional(true)])
676 ]),
677 ( ground(PI)
678 -> atom_pi(PI, Obj)
679 ; ground(Fun)
680 -> atomic_list_concat([Name,ArityAtom], /, Fun),
681 atom_number(ArityAtom, Arity),
682 Obj = f(Name/Arity)
683 ; ground(F)
684 -> Obj = c(F)
685 ; ground(Sec)
686 -> atom_concat('sec:', Sec, SecID),
687 Obj = section(SecID)
688 ),
689 man_title(Obj, Title),
690 reply_html_page(
691 pldoc(object(Obj)),
692 title(Title),
693 \man_page(Obj, [])).
694
695man_title(f(Obj), Title) :-
696 !,
697 format(atom(Title), 'SWI-Prolog -- function ~w', [Obj]).
698man_title(c(Obj), Title) :-
699 !,
700 format(atom(Title), 'SWI-Prolog -- API-function ~w', [Obj]).
701man_title(section(_Id), Title) :-
702 !,
703 format(atom(Title), 'SWI-Prolog -- Manual', []).
704man_title(Obj, Title) :-
705 format(atom(Title), 'SWI-Prolog -- ~w', [Obj]).
706
711
712pldoc_object(Request) :-
713 http_parameters(Request,
714 [ object(Atom, []),
715 header(Header, [default(true)])
716 ]),
717 ( catch(atom_to_term(Atom, Obj, _), error(_,_), fail)
718 -> true
719 ; atom_to_object(Atom, Obj)
720 ),
721 ( prolog:doc_object_title(Obj, Title)
722 -> true
723 ; Title = Atom
724 ),
725 edit_options(Request, EditOptions),
726 reply_html_page(
727 pldoc(object(Obj)),
728 title(Title),
729 \object_page(Obj, [header(Header)|EditOptions])).
730
731
735
736pldoc_search(Request) :-
737 http_parameters(Request,
738 [ for(For,
739 [ optional(true),
740 description('String to search for')
741 ]),
742 page(Page,
743 [ integer,
744 default(1),
745 description('Page of search results to view')
746 ]),
747 in(In,
748 [ oneof([all,app,noapp,man,lib,pack,wiki]),
749 default(all),
750 description('Search everying, application only or manual only')
751 ]),
752 match(Match,
753 [ oneof([name,summary]),
754 default(summary),
755 description('Match only the name or also the summary')
756 ]),
757 resultFormat(Format,
758 [ oneof(long,summary),
759 default(summary),
760 description('Return full documentation or summary-lines')
761 ])
762 ]),
763 edit_options(Request, EditOptions),
764 format(string(Title), 'Prolog search -- ~w', [For]),
765 reply_html_page(pldoc(search(For)),
766 title(Title),
767 \search_reply(For,
768 [ resultFormat(Format),
769 search_in(In),
770 search_match(Match),
771 page(Page)
772 | EditOptions
773 ])).
774
775
776 779
780:- public
781 param/2. 782
783param(public_only,
784 [ boolean,
785 default(true),
786 description('If true, hide private predicates')
787 ]).
788param(reload,
789 [ boolean,
790 default(false),
791 description('Reload the file and its documentation')
792 ]).
793param(show,
794 [ oneof([doc,src,raw]),
795 default(doc),
796 description('How to show the file')
797 ]).
798param(format_comments,
799 [ boolean,
800 default(true),
801 description('If true, use PlDoc for rendering structured comments')
802 ])