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