1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2006-2017, University of Amsterdam 7 VU University Amsterdam 8 All rights reserved. 9 10 Redistribution and use in source and binary forms, with or without 11 modification, are permitted provided that the following conditions 12 are met: 13 14 1. Redistributions of source code must retain the above copyright 15 notice, this list of conditions and the following disclaimer. 16 17 2. Redistributions in binary form must reproduce the above copyright 18 notice, this list of conditions and the following disclaimer in 19 the documentation and/or other materials provided with the 20 distribution. 21 22 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 23 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 24 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 25 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 26 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 27 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 28 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 29 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 30 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 31 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 32 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 33 POSSIBILITY OF SUCH DAMAGE. 34*/ 35 36:- module(pldoc_http, 37 [ doc_enable/1, % +Boolean 38 doc_server/1, % ?Port 39 doc_server/2, % ?Port, +Options 40 doc_browser/0, 41 doc_browser/1 % +What 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:- if(exists_source(library(pce_emacs))). 75:- autoload(library(pce_emacs), [start_emacs/0]). 76:- endif.
85:- dynamic 86 doc_server_port/1, 87 doc_enabled/0. 88 89httplocation(pldoc, root(pldoc), []). 90httplocation(pldoc_man, pldoc(refman), []). 91httplocation(pldoc_pkg, pldoc(package), []). 92httplocation(pldoc_resource, Path, []) :- 93 http_location_by_id(pldoc_resource, Path).
101doc_enable(true) :- 102 ( doc_enabled 103 -> true 104 ; assertz(doc_enabled) 105 ). 106doc_enable(false) :- 107 retractall(doc_enabled).
ip(A,B,C,D)
. See tcp_host_to_address/2 for
details.allow(HostOrIP)
.true
.The predicate doc_server/1 is defined as below, which provides a good default for development.
doc_server(Port) :- doc_server(Port, [ allow(localhost) ]).
143doc_server(Port) :- 144 doc_server(Port, 145 [ allow(localhost), 146 allow(ip(127,0,0,1)) % Windows ip-->host often fails 147 ]). 148 149doc_server(Port, _) :- 150 doc_enable(true), 151 catch(doc_current_server(Port), _, fail), 152 !. 153:- if(current_predicate(http_server/2)). 154doc_server(Port, Options) :- 155 doc_enable(true), 156 prepare_editor, 157 host_access_options(Options, ServerOptions), 158 http_absolute_location(pldoc('.'), Entry, []), 159 merge_options(ServerOptions, 160 [ port(Port), 161 entry_page(Entry) 162 ], HTTPOptions), 163 http_server(http_dispatch, HTTPOptions), 164 assertz(doc_server_port(Port)). 165:- endif.
178doc_current_server(Port) :- 179 ( doc_server_port(P) 180 -> Port = P 181 ; http_current_server(_:_, P) 182 -> Port = P 183 ; existence_error(http_server, pldoc) 184 ). 185 186:- if(\+current_predicate(http_current_server/2)). 187http_current_server(_,_) :- fail. 188:- endif.
195doc_browser :- 196 doc_browser([]). 197doc_browser(Spec) :- 198 catch(doc_current_server(Port), 199 error(existence_error(http_server, pldoc), _), 200 doc_server(Port)), 201 browser_url(Spec, Request), 202 format(string(URL), 'http://localhost:~w~w', [Port, Request]), 203 www_open_url(URL). 204 205browser_url([], Root) :- 206 !, 207 http_location_by_id(pldoc_root, Root). 208browser_url(Name, URL) :- 209 atom(Name), 210 !, 211 browser_url(Name/_, URL). 212browser_url(Name//Arity, URL) :- 213 must_be(atom, Name), 214 integer(Arity), 215 !, 216 PredArity is Arity+2, 217 browser_url(Name/PredArity, URL). 218browser_url(Name/Arity, URL) :- 219 !, 220 must_be(atom, Name), 221 ( man_object_property(Name/Arity, summary(_)) 222 -> format(string(S), '~q/~w', [Name, Arity]), 223 http_link_to_id(pldoc_man, [predicate=S], URL) 224 ; browser_url(_:Name/Arity, URL) 225 ). 226browser_url(Spec, URL) :- 227 !, 228 Spec = M:Name/Arity, 229 doc_comment(Spec, _Pos, _Summary, _Comment), 230 !, 231 ( var(M) 232 -> format(string(S), '~q/~w', [Name, Arity]) 233 ; format(string(S), '~q:~q/~w', [M, Name, Arity]) 234 ), 235 http_link_to_id(pldoc_object, [object=S], URL).
242:- if(current_predicate(start_emacs/0)). 243prepare_editor :- 244 current_prolog_flag(editor, pce_emacs), 245 !, 246 start_emacs. 247:- endif. 248prepare_editor. 249 250 251 /******************************* 252 * USER REPLIES * 253 *******************************/ 254 255:- http_handler(pldoc(.), pldoc_root, 256 [ prefix, 257 authentication(pldoc(read)), 258 condition(doc_enabled) 259 ]). 260:- http_handler(pldoc('index.html'), pldoc_index, []). 261:- http_handler(pldoc(file), pldoc_file, []). 262:- http_handler(pldoc(place), go_place, []). 263:- http_handler(pldoc(edit), pldoc_edit, 264 [authentication(pldoc(edit))]). 265:- http_handler(pldoc(doc), pldoc_doc, [prefix]). 266:- http_handler(pldoc(man), pldoc_man, []). 267:- http_handler(pldoc(doc_for), pldoc_object, [id(pldoc_doc_for)]). 268:- http_handler(pldoc(search), pldoc_search, []). 269:- http_handler(pldoc('res/'), pldoc_resource, [prefix]).
279pldoc_root(Request) :- 280 http_parameters(Request, 281 [ empty(Empty, [ oneof([true,false]), 282 default(false) 283 ]) 284 ]), 285 pldoc_root(Request, Empty). 286 287pldoc_root(Request, false) :- 288 http_location_by_id(pldoc_root, Root), 289 memberchk(path(Path), Request), 290 Root \== Path, 291 !, 292 existence_error(http_location, Path). 293pldoc_root(_Request, false) :- 294 working_directory(Dir0, Dir0), 295 allowed_directory(Dir0), 296 !, 297 ensure_slash_end(Dir0, Dir1), 298 doc_file_href(Dir1, Ref0), 299 atom_concat(Ref0, 'index.html', Index), 300 throw(http_reply(see_other(Index))). 301pldoc_root(Request, _) :- 302 pldoc_index(Request).
310pldoc_index(_Request) :-
311 reply_html_page(pldoc(index),
312 title('SWI-Prolog documentation'),
313 [ \doc_links('', []),
314 h1('SWI-Prolog documentation'),
315 \man_overview([])
316 ]).
323pldoc_file(Request) :-
324 http_parameters(Request,
325 [ file(File, [])
326 ]),
327 ( source_file(File)
328 -> true
329 ; throw(http_reply(forbidden(File)))
330 ),
331 doc_for_file(File, []).
localhost
. The call can
edit files using the file
attribute or a predicate if both
name
and arity
is given and optionally module
.341pldoc_edit(Request) :- 342 http:authenticate(pldoc(edit), Request, _), 343 http_parameters(Request, 344 [ file(File, 345 [ optional(true), 346 description('Name of the file to edit') 347 ]), 348 line(Line, 349 [ optional(true), 350 integer, 351 description('Line in the file') 352 ]), 353 name(Name, 354 [ optional(true), 355 description('Name of a Prolog predicate to edit') 356 ]), 357 arity(Arity, 358 [ integer, 359 optional(true), 360 description('Arity of a Prolog predicate to edit') 361 ]), 362 module(Module, 363 [ optional(true), 364 description('Name of a Prolog module to search for predicate') 365 ]) 366 ]), 367 ( atom(File) 368 -> allowed_file(File) 369 ; true 370 ), 371 ( atom(File), integer(Line) 372 -> Edit = file(File, line(Line)) 373 ; atom(File) 374 -> Edit = file(File) 375 ; atom(Name), integer(Arity) 376 -> ( atom(Module) 377 -> Edit = (Module:Name/Arity) 378 ; Edit = (Name/Arity) 379 ) 380 ), 381 edit(Edit), 382 format('Content-type: text/plain~n~n'), 383 format('Started ~q~n', [edit(Edit)]). 384pldoc_edit(_Request) :- 385 http_location_by_id(pldoc_edit, Location), 386 throw(http_reply(forbidden(Location))).
393go_place(Request) :- 394 http_parameters(Request, 395 [ place(Place, []) 396 ]), 397 places(Place). 398 399places(':packs:') :- 400 !, 401 http_link_to_id(pldoc_pack, [], HREF), 402 throw(http_reply(moved(HREF))). 403places(Dir0) :- 404 expand_alias(Dir0, Dir), 405 ( allowed_directory(Dir) 406 -> format(string(IndexFile), '~w/index.html', [Dir]), 407 doc_file_href(IndexFile, HREF), 408 throw(http_reply(moved(HREF))) 409 ; throw(http_reply(forbidden(Dir))) 410 ).
417allowed_directory(Dir) :- 418 source_directory(Dir), 419 !. 420allowed_directory(Dir) :- 421 working_directory(CWD, CWD), 422 same_file(CWD, Dir). 423allowed_directory(Dir) :- 424 prolog:doc_directory(Dir).
432allowed_file(File) :- 433 source_file(_, File), 434 !. 435allowed_file(File) :- 436 absolute_file_name(File, Canonical), 437 file_directory_name(Canonical, Dir), 438 allowed_directory(Dir).
445pldoc_resource(Request) :- 446 http_location_by_id(pldoc_resource, ResRoot), 447 memberchk(path(Path), Request), 448 atom_concat(ResRoot, File, Path), 449 file(File, Local), 450 http_reply_file(pldoc(Local), [], Request). 451 452file('pldoc.css', 'pldoc.css'). 453file('pllisting.css', 'pllisting.css'). 454file('pldoc.js', 'pldoc.js'). 455file('edit.png', 'edit.png'). 456file('editpred.png', 'editpred.png'). 457file('up.gif', 'up.gif'). 458file('source.png', 'source.png'). 459file('public.png', 'public.png'). 460file('private.png', 'private.png'). 461file('reload.png', 'reload.png'). 462file('favicon.ico', 'favicon.ico'). 463file('h1-bg.png', 'h1-bg.png'). 464file('h2-bg.png', 'h2-bg.png'). 465file('pub-bg.png', 'pub-bg.png'). 466file('priv-bg.png', 'priv-bg.png'). 467file('multi-bg.png', 'multi-bg.png').
Reply documentation of a file. Path is the absolute path of the file for which to return the documentation. Extension is either none, the Prolog extension or the HTML extension.
Note that we reply with pldoc.css if the file basename is pldoc.css to allow for a relative link from any directory.
481pldoc_doc(Request) :- 482 memberchk(path(ReqPath), Request), 483 http_location_by_id(pldoc_doc, Me), 484 atom_concat(Me, AbsFile0, ReqPath), 485 ( sub_atom(ReqPath, _, _, 0, /) 486 -> atom_concat(ReqPath, 'index.html', File), 487 throw(http_reply(moved(File))) 488 ; clean_path(AbsFile0, AbsFile1), 489 expand_alias(AbsFile1, AbsFile), 490 is_absolute_file_name(AbsFile) 491 -> documentation(AbsFile, Request) 492 ). 493 494documentation(Path, Request) :- 495 file_base_name(Path, Base), 496 file(_, Base), % serve pldoc.css, etc. 497 !, 498 http_reply_file(pldoc(Base), [], Request). 499documentation(Path, Request) :- 500 file_name_extension(_, Ext, Path), 501 autolink_extension(Ext, image), 502 http_reply_file(Path, [unsafe(true)], Request). 503documentation(Path, Request) :- 504 Index = '/index.html', 505 sub_atom(Path, _, _, 0, Index), 506 atom_concat(Dir, Index, Path), 507 exists_directory(Dir), % Directory index 508 !, 509 ( allowed_directory(Dir) 510 -> edit_options(Request, EditOptions), 511 doc_for_dir(Dir, EditOptions) 512 ; throw(http_reply(forbidden(Dir))) 513 ). 514documentation(File, Request) :- 515 wiki_file(File, WikiFile), 516 !, 517 ( allowed_file(WikiFile) 518 -> true 519 ; throw(http_reply(forbidden(File))) 520 ), 521 edit_options(Request, Options), 522 doc_for_wiki_file(WikiFile, Options). 523documentation(Path, Request) :- 524 pl_file(Path, File), 525 !, 526 ( allowed_file(File) 527 -> true 528 ; throw(http_reply(forbidden(File))) 529 ), 530 doc_reply_file(File, Request). 531documentation(Path, _) :- 532 throw(http_reply(not_found(Path))). 533 534:- public 535 doc_reply_file/2. 536 537doc_reply_file(File, Request) :- 538 http_parameters(Request, 539 [ public_only(Public), 540 reload(Reload), 541 show(Show), 542 format_comments(FormatComments) 543 ], 544 [ attribute_declarations(param) 545 ]), 546 ( exists_file(File) 547 -> true 548 ; throw(http_reply(not_found(File))) 549 ), 550 ( Reload == true, 551 source_file(File) 552 -> load_files(File, [if(changed), imports([])]) 553 ; true 554 ), 555 edit_options(Request, EditOptions), 556 ( Show == src 557 -> format('Content-type: text/html~n~n', []), 558 source_to_html(File, stream(current_output), 559 [ skin(src_skin(Request, Show, FormatComments)), 560 format_comments(FormatComments) 561 ]) 562 ; Show == raw 563 -> http_reply_file(File, 564 [ unsafe(true), % is already validated 565 mime_type(text/plain) 566 ], Request) 567 ; doc_for_file(File, 568 [ public_only(Public), 569 source_link(true) 570 | EditOptions 571 ]) 572 ). 573 574 575:- public src_skin/5. % called through source_to_html/3. 576 577src_skin(Request, _Show, FormatComments, header, Out) :- 578 memberchk(request_uri(ReqURI), Request), 579 negate(FormatComments, AltFormatComments), 580 replace_parameters(ReqURI, [show(raw)], RawLink), 581 replace_parameters(ReqURI, [format_comments(AltFormatComments)], CmtLink), 582 phrase(html(div(class(src_formats), 583 [ 'View source with ', 584 a(href(CmtLink), \alt_view(AltFormatComments)), 585 ' or as ', 586 a(href(RawLink), raw) 587 ])), Tokens), 588 print_html(Out, Tokens). 589 590alt_view(true) --> 591 html('formatted comments'). 592alt_view(false) --> 593 html('raw comments'). 594 595negate(true, false). 596negate(false, true). 597 598replace_parameters(ReqURI, Extra, URI) :- 599 uri_components(ReqURI, C0), 600 uri_data(search, C0, Search0), 601 ( var(Search0) 602 -> uri_query_components(Search, Extra) 603 ; uri_query_components(Search0, Form0), 604 merge_options(Extra, Form0, Form), 605 uri_query_components(Search, Form) 606 ), 607 uri_data(search, C0, Search, C), 608 uri_components(URI, C).
edit(true)
in Options if the connection is from the
localhost.616edit_options(Request, [edit(true)]) :- 617 catch(http:authenticate(pldoc(edit), Request, _), _, fail), 618 !. 619edit_options(_, []).
624pl_file(File, PlFile) :- 625 file_name_extension(Base, html, File), 626 !, 627 absolute_file_name(Base, 628 PlFile, 629 [ file_errors(fail), 630 file_type(prolog), 631 access(read) 632 ]). 633pl_file(File, File).
640wiki_file(File, TxtFile) :- 641 file_name_extension(_, Ext, File), 642 wiki_file_extension(Ext), 643 !, 644 TxtFile = File. 645wiki_file(File, TxtFile) :- 646 file_base_name(File, Base), 647 autolink_file(Base, wiki), 648 !, 649 TxtFile = File. 650wiki_file(File, TxtFile) :- 651 file_name_extension(Base, html, File), 652 wiki_file_extension(Ext), 653 file_name_extension(Base, Ext, TxtFile), 654 access_file(TxtFile, read). 655 656wiki_file_extension(md). 657wiki_file_extension(txt).
664clean_path(Path0, Path) :- 665 current_prolog_flag(windows, true), 666 sub_atom(Path0, 2, _, _, :), 667 !, 668 sub_atom(Path0, 1, _, 0, Path). 669clean_path(Path, Path).
683pldoc_man(Request) :- 684 http_parameters(Request, 685 [ predicate(PI, [optional(true)]), 686 function(Fun, [optional(true)]), 687 'CAPI'(F, [optional(true)]), 688 section(Sec, [optional(true)]) 689 ]), 690 ( ground(PI) 691 -> atom_pi(PI, Obj) 692 ; ground(Fun) 693 -> atomic_list_concat([Name,ArityAtom], /, Fun), 694 atom_number(ArityAtom, Arity), 695 Obj = f(Name/Arity) 696 ; ground(F) 697 -> Obj = c(F) 698 ; ground(Sec) 699 -> atom_concat('sec:', Sec, SecID), 700 Obj = section(SecID) 701 ), 702 man_title(Obj, Title), 703 reply_html_page( 704 pldoc(object(Obj)), 705 title(Title), 706 \man_page(Obj, [])). 707 708man_title(f(Obj), Title) :- 709 !, 710 format(atom(Title), 'SWI-Prolog -- function ~w', [Obj]). 711man_title(c(Obj), Title) :- 712 !, 713 format(atom(Title), 'SWI-Prolog -- API-function ~w', [Obj]). 714man_title(section(Id), Title) :- 715 !, 716 ( manual_object(section(_L, _N, Id, _F), 717 STitle, _File, _Class, _Offset) 718 -> true 719 ; STitle = 'Manual' 720 ), 721 format(atom(Title), 'SWI-Prolog -- ~w', [STitle]). 722man_title(Obj, Title) :- 723 copy_term(Obj, Copy), 724 numbervars(Copy, 0, _, [singletons(true)]), 725 format(atom(Title), 'SWI-Prolog -- ~p', [Copy]).
732pldoc_object(Request) :-
733 http_parameters(Request,
734 [ object(Atom, []),
735 header(Header, [default(true)])
736 ]),
737 ( catch(atom_to_term(Atom, Obj, _), error(_,_), fail)
738 -> true
739 ; atom_to_object(Atom, Obj)
740 ),
741 ( prolog:doc_object_title(Obj, Title)
742 -> true
743 ; Title = Atom
744 ),
745 edit_options(Request, EditOptions),
746 reply_html_page(
747 pldoc(object(Obj)),
748 title(Title),
749 \object_page(Obj, [header(Header)|EditOptions])).
756pldoc_search(Request) :- 757 http_parameters(Request, 758 [ for(For, 759 [ optional(true), 760 description('String to search for') 761 ]), 762 page(Page, 763 [ integer, 764 default(1), 765 description('Page of search results to view') 766 ]), 767 in(In, 768 [ oneof([all,app,noapp,man,lib,pack,wiki]), 769 default(all), 770 description('Search everying, application only or manual only') 771 ]), 772 match(Match, 773 [ oneof([name,summary]), 774 default(summary), 775 description('Match only the name or also the summary') 776 ]), 777 resultFormat(Format, 778 [ oneof(long,summary), 779 default(summary), 780 description('Return full documentation or summary-lines') 781 ]) 782 ]), 783 edit_options(Request, EditOptions), 784 format(string(Title), 'Prolog search -- ~w', [For]), 785 reply_html_page(pldoc(search(For)), 786 title(Title), 787 \search_reply(For, 788 [ resultFormat(Format), 789 search_in(In), 790 search_match(Match), 791 page(Page) 792 | EditOptions 793 ])). 794 795 796 /******************************* 797 * HTTP PARAMETER TYPES * 798 *******************************/ 799 800:- public 801 param/2. % used in pack documentation server 802 803param(public_only, 804 [ boolean, 805 default(true), 806 description('If true, hide private predicates') 807 ]). 808param(reload, 809 [ boolean, 810 default(false), 811 description('Reload the file and its documentation') 812 ]). 813param(show, 814 [ oneof([doc,src,raw]), 815 default(doc), 816 description('How to show the file') 817 ]). 818param(format_comments, 819 [ boolean, 820 default(true), 821 description('If true, use PlDoc for rendering structured comments') 822 ])
Documentation server
The module
library(pldoc/http)
provides an embedded HTTP documentation server that allows for browsing the documentation of all files loaded after library(pldoc) has been loaded. */