View source with raw comments or as raw
    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:- 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)).

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. */

   79:- dynamic
   80    doc_server_port/1,
   81    doc_enabled/0.   82
   83http:location(pldoc, root(pldoc), []).
   84http:location(pldoc_man, pldoc(refman), []).
   85http:location(pldoc_pkg, pldoc(package), []).
   86http:location(pldoc_resource, Path, []) :-
   87    http_location_by_id(pldoc_resource, Path).
 doc_enable(+Boolean)
Actually activate the PlDoc server. Merely loading the server does not do so to avoid incidental loading in a user HTTP server making the documentation available.
   95doc_enable(true) :-
   96    (   doc_enabled
   97    ->  true
   98    ;   assertz(doc_enabled)
   99    ).
  100doc_enable(false) :-
  101    retractall(doc_enabled).
 doc_server(?Port) is det
 doc_server(?Port, +Options) is det
Start a documentation server in the current Prolog process. The server is started in a seperate thread. Options are handed to http_server/2. In addition, the following options are recognised:
allow(HostOrIP)
Allow connections from HostOrIP. If HostOrIP is an atom it is matched to the hostname. It if starts with a ., suffix match is done, matching the domain. Finally it can be a term ip(A,B,C,D). See tcp_host_to_address/2 for details.
deny(HostOrIP)
See allow(HostOrIP).
edit(Bool)
Allow editing from localhost connections? Default: 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)
                   ]).
See also
- doc_browser/1
  137doc_server(Port) :-
  138    doc_server(Port,
  139               [ allow(localhost),
  140                 allow(ip(127,0,0,1)) % Windows ip-->host often fails
  141               ]).
  142
  143doc_server(Port, _) :-
  144    doc_enable(true),
  145    catch(doc_current_server(Port), _, fail),
  146    !.
  147doc_server(Port, Options) :-
  148    doc_enable(true),
  149    prepare_editor,
  150    host_access_options(Options, ServerOptions),
  151    merge_options(ServerOptions,
  152                  [ port(Port)
  153                  ], HTTPOptions),
  154    http_server(http_dispatch, HTTPOptions),
  155    assertz(doc_server_port(Port)).
 doc_current_server(-Port) is det
TCP/IP port of the documentation server. Fails if no server is running. Note that in the current infrastructure we can easily be embedded into another Prolog HTTP server. If we are not started from doc_server/2, we return the port of a running HTTP server.
Errors
- existence_error(http_server, pldoc)
To be done
- Trap destruction of the server.
  168doc_current_server(Port) :-
  169    (   doc_server_port(P)
  170    ->  Port = P
  171    ;   http_current_server(_:_, P)
  172    ->  Port = P
  173    ;   existence_error(http_server, pldoc)
  174    ).
 doc_browser is det
 doc_browser(+What) is semidet
Open user's default browser on the documentation server.
  181doc_browser :-
  182    doc_browser([]).
  183doc_browser(Spec) :-
  184    catch(doc_current_server(Port),
  185          error(existence_error(http_server, pldoc), _),
  186          doc_server(Port)),
  187    browser_url(Spec, Request),
  188    format(string(URL), 'http://localhost:~w~w', [Port, Request]),
  189    www_open_url(URL).
  190
  191browser_url([], Root) :-
  192    !,
  193    http_location_by_id(pldoc_root, Root).
  194browser_url(Name, URL) :-
  195    atom(Name),
  196    !,
  197    browser_url(Name/_, URL).
  198browser_url(Name//Arity, URL) :-
  199    must_be(atom, Name),
  200    integer(Arity),
  201    !,
  202    PredArity is Arity+2,
  203    browser_url(Name/PredArity, URL).
  204browser_url(Name/Arity, URL) :-
  205    !,
  206    must_be(atom, Name),
  207    (   predicate(Name, Arity, _, _, _)
  208    ->  format(string(S), '~q/~w', [Name, Arity]),
  209        http_link_to_id(pldoc_man, [predicate=S], URL)
  210    ;   browser_url(_:Name/Arity, URL)
  211    ).
  212browser_url(Spec, URL) :-
  213    !,
  214    Spec = M:Name/Arity,
  215    doc_comment(Spec, _Pos, _Summary, _Comment),
  216    !,
  217    (   var(M)
  218    ->  format(string(S), '~q/~w', [Name, Arity])
  219    ;   format(string(S), '~q:~q/~w', [M, Name, Arity])
  220    ),
  221    http_link_to_id(pldoc_object, [object=S], URL).
 prepare_editor
Start XPCE as edit requests comming from the document server can only be handled if XPCE is running.
  228prepare_editor :-
  229    current_prolog_flag(editor, pce_emacs),
  230    !,
  231    start_emacs.
  232prepare_editor.
  233
  234
  235                 /*******************************
  236                 *          USER REPLIES        *
  237                 *******************************/
  238
  239:- http_handler(pldoc(.),          pldoc_root,
  240                [ prefix,
  241                  authentication(pldoc(read)),
  242                  condition(doc_enabled)
  243                ]).  244:- http_handler(pldoc('index.html'), pldoc_index,   []).  245:- http_handler(pldoc(file),       pldoc_file,     []).  246:- http_handler(pldoc(place),      go_place,       []).  247:- http_handler(pldoc(edit),       pldoc_edit,
  248                [authentication(pldoc(edit))]).  249:- http_handler(pldoc(doc),        pldoc_doc,      [prefix]).  250:- http_handler(pldoc(man),        pldoc_man,      []).  251:- http_handler(pldoc(doc_for),    pldoc_object,   [id(pldoc_doc_for)]).  252:- http_handler(pldoc(search),     pldoc_search,   []).  253:- http_handler(pldoc('res/'),     pldoc_resource, [prefix]).
 pldoc_root(+Request)
Reply using the index-page of the Prolog working directory. There are various options for the start directory. For example we could also use the file or directory of the file that would be edited using edit/0.
  263pldoc_root(Request) :-
  264    http_parameters(Request,
  265                    [ empty(Empty, [ oneof([true,false]),
  266                                     default(false)
  267                                   ])
  268                    ]),
  269    pldoc_root(Request, Empty).
  270
  271pldoc_root(Request, false) :-
  272    http_location_by_id(pldoc_root, Root),
  273    memberchk(path(Path), Request),
  274    Root \== Path,
  275    !,
  276    existence_error(http_location, Path).
  277pldoc_root(_Request, false) :-
  278    working_directory(Dir0, Dir0),
  279    allowed_directory(Dir0),
  280    !,
  281    ensure_slash_end(Dir0, Dir1),
  282    doc_file_href(Dir1, Ref0),
  283    atom_concat(Ref0, 'index.html', Index),
  284    throw(http_reply(see_other(Index))).
  285pldoc_root(Request, _) :-
  286    pldoc_index(Request).
 pldoc_index(+Request)
HTTP handle for /index.html, providing an overall overview of the available documentation.
  294pldoc_index(_Request) :-
  295    reply_html_page(pldoc(index),
  296                    title('SWI-Prolog documentation'),
  297                    [ \doc_links('', []),
  298                       h1('SWI-Prolog documentation'),
  299                      \man_overview([])
  300                    ]).
 pldoc_file(+Request)
Hander for /file?file=File, providing documentation for File.
  307pldoc_file(Request) :-
  308    http_parameters(Request,
  309                    [ file(File, [])
  310                    ]),
  311    (   source_file(File)
  312    ->  true
  313    ;   throw(http_reply(forbidden(File)))
  314    ),
  315    doc_for_file(File, []).
 pldoc_edit(+Request)
HTTP handler that starts the user's default editor on the host running the server. This handler can only accessed if the browser connection originates from localhost. The call can edit files using the file attribute or a predicate if both name and arity is given and optionally module.
  325pldoc_edit(Request) :-
  326    http:authenticate(pldoc(edit), Request, _),
  327    http_parameters(Request,
  328                    [ file(File,
  329                           [ optional(true),
  330                             description('Name of the file to edit')
  331                           ]),
  332                      line(Line,
  333                           [ optional(true),
  334                             integer,
  335                             description('Line in the file')
  336                           ]),
  337                      name(Name,
  338                           [ optional(true),
  339                             description('Name of a Prolog predicate to edit')
  340                           ]),
  341                      arity(Arity,
  342                            [ integer,
  343                              optional(true),
  344                              description('Arity of a Prolog predicate to edit')
  345                            ]),
  346                      module(Module,
  347                             [ optional(true),
  348                               description('Name of a Prolog module to search for predicate')
  349                             ])
  350                    ]),
  351    (   atom(File)
  352    ->  allowed_file(File)
  353    ;   true
  354    ),
  355    (   atom(File), integer(Line)
  356    ->  Edit = file(File, line(Line))
  357    ;   atom(File)
  358    ->  Edit = file(File)
  359    ;   atom(Name), integer(Arity)
  360    ->  (   atom(Module)
  361        ->  Edit = (Module:Name/Arity)
  362        ;   Edit = (Name/Arity)
  363        )
  364    ),
  365    edit(Edit),
  366    format('Content-type: text/plain~n~n'),
  367    format('Started ~q~n', [edit(Edit)]).
  368pldoc_edit(_Request) :-
  369    http_location_by_id(pldoc_edit, Location),
  370    throw(http_reply(forbidden(Location))).
 go_place(+Request)
HTTP handler to handle the places menu.
  377go_place(Request) :-
  378    http_parameters(Request,
  379                    [ place(Place, [])
  380                    ]),
  381    places(Place).
  382
  383places(':packs:') :-
  384    !,
  385    http_link_to_id(pldoc_pack, [], HREF),
  386    throw(http_reply(moved(HREF))).
  387places(Dir0) :-
  388    expand_alias(Dir0, Dir),
  389    (   allowed_directory(Dir)
  390    ->  format(string(IndexFile), '~w/index.html', [Dir]),
  391        doc_file_href(IndexFile, HREF),
  392        throw(http_reply(moved(HREF)))
  393    ;   throw(http_reply(forbidden(Dir)))
  394    ).
 allowed_directory(+Dir) is semidet
True if we are allowed to produce and index for Dir.
  401allowed_directory(Dir) :-
  402    source_directory(Dir),
  403    !.
  404allowed_directory(Dir) :-
  405    working_directory(CWD, CWD),
  406    same_file(CWD, Dir).
  407allowed_directory(Dir) :-
  408    prolog:doc_directory(Dir).
 allowed_file(+File) is semidet
True if we are allowed to serve File. Currently means we have predicates loaded from File or the directory must be allowed.
  416allowed_file(File) :-
  417    source_file(_, File),
  418    !.
  419allowed_file(File) :-
  420    absolute_file_name(File, Canonical),
  421    file_directory_name(Canonical, Dir),
  422    allowed_directory(Dir).
 pldoc_resource(+Request)
Handler for /res/File, serving CSS, JS and image files.
  429pldoc_resource(Request) :-
  430    http_location_by_id(pldoc_resource, ResRoot),
  431    memberchk(path(Path), Request),
  432    atom_concat(ResRoot, File, Path),
  433    file(File, Local),
  434    http_reply_file(pldoc(Local), [], Request).
  435
  436file('pldoc.css',     'pldoc.css').
  437file('pllisting.css', 'pllisting.css').
  438file('pldoc.js',      'pldoc.js').
  439file('edit.png',      'edit.png').
  440file('editpred.png',  'editpred.png').
  441file('up.gif',        'up.gif').
  442file('source.png',    'source.png').
  443file('public.png',    'public.png').
  444file('private.png',   'private.png').
  445file('reload.png',    'reload.png').
  446file('favicon.ico',   'favicon.ico').
  447file('h1-bg.png',     'h1-bg.png').
  448file('h2-bg.png',     'h2-bg.png').
  449file('pub-bg.png',    'pub-bg.png').
  450file('priv-bg.png',   'priv-bg.png').
  451file('multi-bg.png',  'multi-bg.png').
 pldoc_doc(+Request)
Handler for /doc/Path

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.

  465pldoc_doc(Request) :-
  466    memberchk(path(ReqPath), Request),
  467    http_location_by_id(pldoc_doc, Me),
  468    atom_concat(Me, AbsFile0, ReqPath),
  469    (   sub_atom(ReqPath, _, _, 0, /)
  470    ->  atom_concat(ReqPath, 'index.html', File),
  471        throw(http_reply(moved(File)))
  472    ;   clean_path(AbsFile0, AbsFile1),
  473        expand_alias(AbsFile1, AbsFile),
  474        is_absolute_file_name(AbsFile)
  475    ->  documentation(AbsFile, Request)
  476    ).
  477
  478documentation(Path, Request) :-
  479    file_base_name(Path, Base),
  480    file(_, Base),                         % serve pldoc.css, etc.
  481    !,
  482    http_reply_file(pldoc(Base), [], Request).
  483documentation(Path, Request) :-
  484    file_name_extension(_, Ext, Path),
  485    autolink_extension(Ext, image),
  486    http_reply_file(Path, [unsafe(true)], Request).
  487documentation(Path, Request) :-
  488    Index = '/index.html',
  489    sub_atom(Path, _, _, 0, Index),
  490    atom_concat(Dir, Index, Path),
  491    exists_directory(Dir),                 % Directory index
  492    !,
  493    (   allowed_directory(Dir)
  494    ->  edit_options(Request, EditOptions),
  495        doc_for_dir(Dir, EditOptions)
  496    ;   throw(http_reply(forbidden(Dir)))
  497    ).
  498documentation(File, Request) :-
  499    wiki_file(File, WikiFile),
  500    !,
  501    (   allowed_file(WikiFile)
  502    ->  true
  503    ;   throw(http_reply(forbidden(File)))
  504    ),
  505    edit_options(Request, Options),
  506    doc_for_wiki_file(WikiFile, Options).
  507documentation(Path, Request) :-
  508    pl_file(Path, File),
  509    !,
  510    (   allowed_file(File)
  511    ->  true
  512    ;   throw(http_reply(forbidden(File)))
  513    ),
  514    doc_reply_file(File, Request).
  515documentation(Path, _) :-
  516    throw(http_reply(not_found(Path))).
  517
  518:- public
  519    doc_reply_file/2.  520
  521doc_reply_file(File, Request) :-
  522    http_parameters(Request,
  523                    [ public_only(Public),
  524                      reload(Reload),
  525                      show(Show),
  526                      format_comments(FormatComments)
  527                    ],
  528                    [ attribute_declarations(param)
  529                    ]),
  530    (   exists_file(File)
  531    ->  true
  532    ;   throw(http_reply(not_found(File)))
  533    ),
  534    (   Reload == true,
  535        source_file(File)
  536    ->  load_files(File, [if(changed), imports([])])
  537    ;   true
  538    ),
  539    edit_options(Request, EditOptions),
  540    (   Show == src
  541    ->  format('Content-type: text/html~n~n', []),
  542        source_to_html(File, stream(current_output),
  543                       [ skin(src_skin(Request, Show, FormatComments)),
  544                         format_comments(FormatComments)
  545                       ])
  546    ;   Show == raw
  547    ->  http_reply_file(File,
  548                        [ unsafe(true), % is already validated
  549                          mime_type(text/plain)
  550                        ], Request)
  551    ;   doc_for_file(File,
  552                     [ public_only(Public),
  553                       source_link(true)
  554                     | EditOptions
  555                     ])
  556    ).
  557
  558
  559:- public src_skin/5.                   % called through source_to_html/3.
  560
  561src_skin(Request, _Show, FormatComments, header, Out) :-
  562    memberchk(request_uri(ReqURI), Request),
  563    negate(FormatComments, AltFormatComments),
  564    replace_parameters(ReqURI, [show(raw)], RawLink),
  565    replace_parameters(ReqURI, [format_comments(AltFormatComments)], CmtLink),
  566    phrase(html(div(class(src_formats),
  567                    [ 'View source with ',
  568                      a(href(CmtLink), \alt_view(AltFormatComments)),
  569                      ' or as ',
  570                      a(href(RawLink), raw)
  571                    ])), Tokens),
  572    print_html(Out, Tokens).
  573
  574alt_view(true) -->
  575    html('formatted comments').
  576alt_view(false) -->
  577    html('raw comments').
  578
  579negate(true, false).
  580negate(false, true).
  581
  582replace_parameters(ReqURI, Extra, URI) :-
  583    uri_components(ReqURI, C0),
  584    uri_data(search, C0, Search0),
  585    (   var(Search0)
  586    ->  uri_query_components(Search, Extra)
  587    ;   uri_query_components(Search0, Form0),
  588        merge_options(Extra, Form0, Form),
  589        uri_query_components(Search, Form)
  590    ),
  591    uri_data(search, C0, Search, C),
  592    uri_components(URI, C).
 edit_options(+Request, -Options) is det
Return edit(true) in Options if the connection is from the localhost.
  600edit_options(Request, [edit(true)]) :-
  601    catch(http:authenticate(pldoc(edit), Request, _), _, fail),
  602    !.
  603edit_options(_, []).
 pl_file(+File, -PlFile) is semidet
  608pl_file(File, PlFile) :-
  609    file_name_extension(Base, html, File),
  610    !,
  611    absolute_file_name(Base,
  612                       PlFile,
  613                       [ file_errors(fail),
  614                         file_type(prolog),
  615                         access(read)
  616                       ]).
  617pl_file(File, File).
 wiki_file(+File, -TxtFile) is semidet
True if TxtFile is an existing file that must be served as wiki file.
  624wiki_file(File, TxtFile) :-
  625    file_name_extension(_, Ext, File),
  626    wiki_file_extension(Ext),
  627    !,
  628    TxtFile = File.
  629wiki_file(File, TxtFile) :-
  630    file_base_name(File, Base),
  631    autolink_file(Base, wiki),
  632    !,
  633    TxtFile = File.
  634wiki_file(File, TxtFile) :-
  635    file_name_extension(Base, html, File),
  636    wiki_file_extension(Ext),
  637    file_name_extension(Base, Ext, TxtFile),
  638    access_file(TxtFile, read).
  639
  640wiki_file_extension(md).
  641wiki_file_extension(txt).
 clean_path(+AfterDoc, -AbsPath)
Restore the path, Notably deals Windows issues
  648clean_path(Path0, Path) :-
  649    current_prolog_flag(windows, true),
  650    sub_atom(Path0, 2, _, _, :),
  651    !,
  652    sub_atom(Path0, 1, _, 0, Path).
  653clean_path(Path, Path).
 pldoc_man(+Request)
Handler for /man, offering one of the parameters:
predicate=PI
providing documentation from the manual on the predicate PI.
function=PI
providing documentation from the manual on the function PI.
CAPI=F
providing documentation from the manual on the C-function F.
  667pldoc_man(Request) :-
  668    http_parameters(Request,
  669                    [ predicate(PI, [optional(true)]),
  670                      function(Fun, [optional(true)]),
  671                      'CAPI'(F,     [optional(true)]),
  672                      section(Sec,  [optional(true)])
  673                    ]),
  674    (   ground(PI)
  675    ->  atom_pi(PI, Obj)
  676    ;   ground(Fun)
  677    ->  atomic_list_concat([Name,ArityAtom], /, Fun),
  678        atom_number(ArityAtom, Arity),
  679        Obj = f(Name/Arity)
  680    ;   ground(F)
  681    ->  Obj = c(F)
  682    ;   ground(Sec)
  683    ->  atom_concat('sec:', Sec, SecID),
  684        Obj = section(SecID)
  685    ),
  686    man_title(Obj, Title),
  687    reply_html_page(
  688        pldoc(object(Obj)),
  689        title(Title),
  690        \man_page(Obj, [])).
  691
  692man_title(f(Obj), Title) :-
  693    !,
  694    format(atom(Title), 'SWI-Prolog -- function ~w', [Obj]).
  695man_title(c(Obj), Title) :-
  696    !,
  697    format(atom(Title), 'SWI-Prolog -- API-function ~w', [Obj]).
  698man_title(section(_Id), Title) :-
  699    !,
  700    format(atom(Title), 'SWI-Prolog -- Manual', []).
  701man_title(Obj, Title) :-
  702    format(atom(Title), 'SWI-Prolog -- ~w', [Obj]).
 pldoc_object(+Request)
Handler for /doc_for?object=Term, Provide documentation for the given term.
  709pldoc_object(Request) :-
  710    http_parameters(Request,
  711                    [ object(Atom, []),
  712                      header(Header, [default(true)])
  713                    ]),
  714    atom_to_term(Atom, Obj, _),
  715    (   prolog:doc_object_title(Obj, Title)
  716    ->  true
  717    ;   Title = Atom
  718    ),
  719    edit_options(Request, EditOptions),
  720    reply_html_page(
  721        pldoc(object(Obj)),
  722        title(Title),
  723        \object_page(Obj, [header(Header)|EditOptions])).
 pldoc_search(+Request)
Search the collected PlDoc comments and Prolog manual.
  730pldoc_search(Request) :-
  731    http_parameters(Request,
  732                    [ for(For,
  733                          [ optional(true),
  734                            description('String to search for')
  735                          ]),
  736                      in(In,
  737                         [ oneof([all,app,man]),
  738                           default(all),
  739                           description('Search everying, application only or manual only')
  740                         ]),
  741                      match(Match,
  742                            [ oneof([name,summary]),
  743                              default(summary),
  744                              description('Match only the name or also the summary')
  745                            ]),
  746                      resultFormat(Format,
  747                                   [ oneof(long,summary),
  748                                     default(summary),
  749                                     description('Return full documentation or summary-lines')
  750                                   ])
  751                    ]),
  752    edit_options(Request, EditOptions),
  753    format(string(Title), 'Prolog search -- ~w', [For]),
  754    reply_html_page(pldoc(search(For)),
  755                    title(Title),
  756                    \search_reply(For,
  757                                  [ resultFormat(Format),
  758                                    search_in(In),
  759                                    search_match(Match)
  760                                  | EditOptions
  761                                  ])).
  762
  763
  764                 /*******************************
  765                 *     HTTP PARAMETER TYPES     *
  766                 *******************************/
  767
  768:- public
  769    param/2.                        % used in pack documentation server
  770
  771param(public_only,
  772      [ boolean,
  773        default(true),
  774        description('If true, hide private predicates')
  775      ]).
  776param(reload,
  777      [ boolean,
  778        default(false),
  779        description('Reload the file and its documentation')
  780      ]).
  781param(show,
  782      [ oneof([doc,src,raw]),
  783        default(doc),
  784        description('How to show the file')
  785      ]).
  786param(format_comments,
  787      [ boolean,
  788        default(true),
  789        description('If true, use PlDoc for rendering structured comments')
  790      ])