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_man,
   37          [ clean_man_index/0,          %
   38            index_man_directory/2,      % +DirSpec, +Options
   39            index_man_file/2,           % +Class, +FileSpec
   40            current_man_object/1,       % ?Object
   41                                        % HTML generation
   42            man_page//2,                % +Obj, +Options
   43            man_overview//1,            % +Options
   44
   45            man_content_tree/2,         % +Dir, -Tree
   46            man_packages_tree/1         % -Tree
   47          ]).   48:- use_module(library(sgml)).   49:- use_module(library(occurs)).   50:- use_module(library(lists)).   51:- use_module(library(uri)).   52:- use_module(library(apply)).   53:- use_module(library(option)).   54:- use_module(library(filesex)).   55:- use_module(library(xpath)).   56:- use_module(doc_wiki).   57:- use_module(doc_html).   58:- use_module(doc_search).   59:- use_module(doc_process).   60:- use_module(doc_util).   61:- use_module(library(http/html_write)).   62:- use_module(library(http/html_head)).   63:- use_module(library(http/http_dispatch)).   64:- use_module(library(http/http_path)).   65:- use_module(library(http/mimetype)).   66:- include(hooks).

Process SWI-Prolog HTML manuals

*/

   72:- predicate_options(index_man_directory/2, 2,
   73                     [ class(oneof([manual,packages,misc])),
   74                       pass_to(system:absolute_file_name/3, 3)
   75                     ]).   76:- predicate_options(man_page//2, 2,
   77                     [ for(atom),
   78                       links(boolean),
   79                       navtree(boolean),
   80                       footer(boolean),
   81                       no_manual(oneof([fail,error])),
   82                       search_in(oneof([all, app, man])),
   83                       search_match(oneof([name, summary])),
   84                       search_options(boolean)
   85                     ]).   86
   87
   88:- dynamic
   89    man_index/5.            % Object, Summary, File, Class, Offset
 clean_man_index is det
Clean already loaded manual index.
   95clean_man_index :-
   96    retractall(man_index(_,_,_,_,_)).
 manual_directory(-Class, -Dir)// is nondet
True if Dir is a directory holding manual files. Class is an identifier used by doc_object_summary/4.
  104manual_directory(manual,   swi('doc/Manual')).
  105manual_directory(packages, swi('doc/packages')).
  106
  107
  108                 /*******************************
  109                 *          PARSE MANUAL        *
  110                 *******************************/
 index_manual is det
Load the manual index if not already done.
  116index_manual :-
  117    man_index(_,_,_,_,_),
  118    !.
  119index_manual :-
  120    with_mutex(pldoc_man,
  121               locked_index_manual).
  122
  123locked_index_manual :-
  124    man_index(_,_,_,_,_),
  125    !.
  126locked_index_manual :-
  127    (   manual_directory(Class, Dir),
  128        index_man_directory(Dir,
  129                            [ class(Class),
  130                              file_errors(fail)
  131                            ]),
  132        fail ; true
  133    ).
  134
  135check_duplicate_ids :-
  136    findall(Id, man_index(section(_,_,Id,_),_,_,_,_), Ids),
  137    msort(Ids, Sorted),
  138    duplicate_ids(Sorted, Duplicates),
  139    (   Duplicates == []
  140    ->  true
  141    ;   print_message(warning, pldoc(duplicate_ids(Duplicates)))
  142    ).
  143
  144duplicate_ids([], []).
  145duplicate_ids([H,H|T0], [H|D]) :-
  146    !,
  147    take_prefix(H,T0,T),
  148    duplicate_ids(T, D).
  149duplicate_ids([_|T], D) :-
  150    duplicate_ids(T, D).
  151
  152take_prefix(H, [H|T0], T) :-
  153    !,
  154    take_prefix(H, T0, T).
  155take_prefix(_, L, L).
 index_man_directory(Dir, +Options) is det
Index the HTML directory Dir. Options are:
class(Class)
Define category of the found objects.

Remaining Options are passed to absolute_file_name/3.

  167index_man_directory(Spec, Options) :-
  168    select_option(class(Class), Options, Options1, misc),
  169    absolute_file_name(Spec, Dir,
  170                       [ file_type(directory),
  171                         access(read)
  172                       | Options1
  173                       ]),
  174    atom_concat(Dir, '/*.html', Pattern),
  175    expand_file_name(Pattern, Files),
  176    maplist(index_man_file(Class), Files).
 index_man_file(+Class, +File)
Collect the documented objects from the SWI-Prolog manual file File.
  184index_man_file(Class, File) :-
  185    absolute_file_name(File, Path,
  186                       [ access(read)
  187                       ]),
  188    open(Path, read, In, [type(binary)]),
  189    dtd(html, DTD),
  190    new_sgml_parser(Parser, [dtd(DTD)]),
  191    set_sgml_parser(Parser, file(File)),
  192    set_sgml_parser(Parser, dialect(sgml)),
  193    set_sgml_parser(Parser, shorttag(false)),
  194    nb_setval(pldoc_man_index, []),
  195    nb_setval(pldoc_index_class, Class),
  196    call_cleanup(sgml_parse(Parser,
  197                            [ source(In),
  198                              syntax_errors(quiet),
  199                              call(begin, index_on_begin)
  200                            ]),
  201                 (   free_sgml_parser(Parser),
  202                     close(In),
  203                     nb_delete(pldoc_man_index)
  204                 )).
 index_on_begin(+Element, +Attributes, +Parser) is semidet
Called from sgml_parse/2 in index_man_file/2. Element is the name of the element, Attributes the list of Name=Value pairs of the open attributes. Parser is the parser objects.
  213index_on_begin(dt, Attributes, Parser) :-
  214    memberchk(class=pubdef, Attributes),
  215    get_sgml_parser(Parser, charpos(Offset)),
  216    get_sgml_parser(Parser, file(File)),
  217    sgml_parse(Parser,
  218               [ document(DT),
  219                 syntax_errors(quiet),
  220                 parse(content)
  221               ]),
  222    (   sub_term(element(a, AA, _), DT),
  223        member(Attr, ['data-obj', id, name]),
  224        memberchk(Attr=Id, AA),
  225        name_to_object(Id, PI)
  226    ->  true
  227    ),
  228    nb_getval(pldoc_man_index, DD0),
  229    (   memberchk(dd(PI, File, _), DD0)
  230    ->  true
  231    ;   nb_setval(pldoc_man_index, [dd(PI, File, Offset)|DD0])
  232    ).
  233index_on_begin(dd, _, Parser) :-
  234    !,
  235    nb_getval(pldoc_man_index, DDList0), DDList0 \== [],
  236    nb_setval(pldoc_man_index, []),
  237    sgml_parse(Parser,
  238               [ document(DD),
  239                 syntax_errors(quiet),
  240                 parse(content)
  241               ]),
  242    summary(DD, Summary),
  243    nb_getval(pldoc_index_class, Class),
  244    reverse(DDList0, [dd(Object, File, Offset)|DDTail]),
  245    assertz(man_index(Object, Summary, File, Class, Offset)),
  246    forall(member(dd(Obj2,_,_), DDTail),
  247           assertz(man_index(Obj2, Summary, File, Class, Offset))).
  248index_on_begin(div, Attributes, Parser) :-
  249    !,
  250    memberchk(class=title, Attributes),
  251    get_sgml_parser(Parser, charpos(Offset)),
  252    get_sgml_parser(Parser, file(File)),
  253    sgml_parse(Parser,
  254               [ document(DOM),
  255                 syntax_errors(quiet),
  256                 parse(content)
  257               ]),
  258    dom_to_text(DOM, Title),
  259    nb_getval(pldoc_index_class, Class),
  260    swi_local_path(File, Local),
  261    assertz(man_index(section(0, '0', Local, File),
  262                      Title, File, Class, Offset)).
  263index_on_begin(H, Attributes, Parser) :- % TBD: add class for document title.
  264    heading(H, Level),
  265    get_sgml_parser(Parser, charpos(Offset)),
  266    get_sgml_parser(Parser, file(File)),
  267    sgml_parse(Parser,
  268               [ document(Doc),
  269                 syntax_errors(quiet),
  270                 parse(content)
  271               ]),
  272    dom_section(Doc, Nr, Title),
  273    nb_getval(pldoc_index_class, Class),
  274    section_id(Attributes, Title, File, ID),
  275    assertz(man_index(section(Level, Nr, ID, File),
  276                      Title, File, Class, Offset)).
  277
  278section_id(Attributes, _Title, _, ID) :-
  279    memberchk(id=ID, Attributes),
  280    !.
  281section_id(_, "Bibliography", _, 'sec:bibliography') :- !.
  282section_id(_Attributes, Title, File, ID) :-
  283    atomic_list_concat(Words, ' ', Title),
  284    atomic_list_concat(Words, '_', ID0),
  285    atom_concat('sec:', ID0, ID),
  286    print_message(warning, pldoc(no_section_id(File, Title))).
 dom_section(+HeaderDOM, -NR, -Title) is semidet
NR is the section number (e.g. 1.1, 1.23) and Title is the title from a section header. The first clauses processes the style information from latex2html, emitting sections as:
<HN> <A name="sec:nr"><span class='sec-nr'>NR</span>|_|
                      <span class='sec-title'>Title</span>
  299dom_section(DOM, Nr, Title) :-
  300    sub_term([ element(span, A1, [Nr]) | Rest ], DOM),
  301    append(_Sep, [element(span, A2, TitleDOM)], Rest),
  302    memberchk(class='sec-nr', A1),
  303    memberchk(class='sec-title', A2),
  304    !,
  305    dom_to_text(TitleDOM, Title).
  306dom_section(DOM, Nr, Title) :-
  307    dom_to_text(DOM, Title),
  308    section_number(Title, Nr, Title).
  309
  310section_number(Title, Nr, PlainTitle) :-
  311    sub_atom(Title, 0, 1, _, Start),
  312    (   char_type(Start, digit)
  313    ->  true
  314    ;   char_type(Start, upper),
  315        sub_atom(Title, 1, 1, _, '.')       % A., etc: Appendices
  316    ),
  317    sub_atom(Title, B, _, A, ' '),
  318    !,
  319    sub_atom(Title, 0, B, _, Nr),
  320    sub_string(Title, _, A, 0, PlainTitle).
  321
  322heading(h1, 1).
  323heading(h2, 2).
  324heading(h3, 3).
  325heading(h4, 4).
 summary(+DOM, -Summary:string) is det
Summary is the first sentence of DOM.
  332summary(DOM, Summary) :-
  333    phrase(summary(DOM, _), SummaryCodes0),
  334    phrase(normalise_white_space(SummaryCodes), SummaryCodes0),
  335    string_codes(Summary, SummaryCodes).
  336
  337summary([], _) -->
  338    !,
  339    [].
  340summary(_, Done) -->
  341    { Done == true },
  342    !,
  343    [].
  344summary([element(_,_,Content)|T], Done) -->
  345    !,
  346    summary(Content, Done),
  347    summary(T, Done).
  348summary([CDATA|T], Done) -->
  349    { atom_codes(CDATA, Codes)
  350    },
  351    (   { Codes = [Period|Rest],
  352          code_type(Period, period),
  353          space(Rest)
  354        }
  355    ->  [ Period ],
  356        { Done = true }
  357    ;   { append(Sentence, [C, Period|Rest], Codes),
  358          code_type(Period, period),
  359          \+ code_type(C, period),
  360          space(Rest)
  361        }
  362    ->  string(Sentence),
  363        [C, Period],
  364        { Done = true }
  365    ;   string(Codes),
  366        summary(T, Done)
  367    ).
  368
  369string([]) -->
  370    [].
  371string([H|T]) -->
  372    [H],
  373    string(T).
  374
  375space([C|_]) :- code_type(C, space), !.
  376space([]).
 dom_to_text(+DOM, -Text)
Extract the text of a parsed HTML term. White-space in the result is normalised. See normalise_white_space//1.
  383dom_to_text(Dom, Text) :-
  384    phrase(cdata_list(Dom), CDATA),
  385    with_output_to(codes(Codes0),
  386                   forall(member(T, CDATA),
  387                          write(T))),
  388    phrase(normalise_white_space(Codes), Codes0),
  389    string_codes(Text, Codes).
  390
  391cdata_list([]) -->
  392    [].
  393cdata_list([H|T]) -->
  394    cdata(H),
  395    cdata_list(T).
  396
  397cdata(element(_, _, Content)) -->
  398    !,
  399    cdata_list(Content).
  400cdata(CDATA) -->
  401    { atom(CDATA) },
  402    !,
  403    [CDATA].
  404cdata(_) -->
  405    [].
 current_man_object(?Object) is nondet
  409current_man_object(Object) :-
  410    index_manual,
  411    man_index(Object, _, _, _, _).
  412
  413
  414                 /*******************************
  415                 *           HIERARCHY          *
  416                 *******************************/
 man_nav_tree(+Obj, +Options) is semidet
Create a navigation tree consisting of a nested ul list that reflects the location of Obj in the manual.
  423man_nav_tree(Obj, Options) -->
  424    { ensure_man_tree,
  425      man_nav_tree(Obj, Tree, Options),
  426      TreeOptions = [ secref_style(title)
  427                    | Options
  428                    ]
  429    },
  430    html(ul(class(nav),
  431            \object_tree(Tree, [Obj], TreeOptions))).
 man_nav_tree(+Obj, -Tree, +Options) is semidet
True when Tree is the navigation tree for Obj. By default, this is the tree going from the leaf to the root, unfolding the neighbors of Obj.
  440man_nav_tree(Obj, Tree, _Options) :-
  441    man_child_of(Obj, Parent),
  442    !,
  443    findall(Neighbour, man_child_of(Neighbour, Parent), Neighbours0),
  444    (   findall(Child, man_child_of(Child, Obj), Children),
  445        Children \== []
  446    ->  select(Obj, Neighbours0, node(Obj, Children), Neighbours)
  447    ;   Neighbours = Neighbours0
  448    ),
  449    path_up(node(Parent, Neighbours), Tree).
  450man_nav_tree(Obj, node(Obj, Children), _Options) :-
  451    findall(Child, man_child_of(Child, Obj), Children).
  452
  453
  454path_up(Node, Tree) :-
  455    node_id(Node, Id),
  456    man_child_of(Id, Parent),
  457    !,
  458    (   Parent == root
  459    ->  findall(Neighbour, man_child_of(Neighbour, Parent), Neighbours0),
  460        select(Id, Neighbours0, Node, Neighbours),
  461        Tree = node(root, Neighbours)
  462    ;   path_up(node(Parent, [Node]), Tree)
  463    ).
  464path_up(Tree, Tree).
 man_child_of(?Child, ?Parent) is nondet
Query the manual hierarchy.
  471man_child_of(Child, Parent) :-
  472    term_hash(Child, ChildHash),
  473    term_hash(Parent, ParentHash),
  474    man_child_of(ChildHash, Child, ParentHash, Parent).
  475
  476:- dynamic
  477    man_child_of/4,
  478    man_tree_done/0.
 ensure_man_tree
Materialize the manual tree as a binary relation.
  484ensure_man_tree :-
  485    man_tree_done,
  486    !.
  487ensure_man_tree :-
  488    with_mutex(man_tree,
  489               make_man_tree).
  490
  491make_man_tree :-
  492    man_tree_done,
  493    !.
  494make_man_tree :-
  495    man_content_tree(swi('doc/Manual'), ManTree),
  496    man_packages_tree(PkgTree),
  497    assert_tree(node(root, [ManTree, PkgTree])),
  498    assertz(man_tree_done).
  499
  500assert_tree(node(Id, Children)) :-
  501    !,
  502    maplist(assert_parent(Id), Children),
  503    maplist(assert_tree, Children).
  504assert_tree(_).
  505
  506assert_parent(Id, Child) :-
  507    node_id(Child, ChildId),
  508    term_hash(Id, ParentHash),
  509    term_hash(ChildId, ChildHash),
  510    assertz(man_child_of(ChildHash, ChildId, ParentHash, Id)).
  511
  512node_id(node(Id, _), Id) :- !.
  513node_id(Id, Id).
 man_content_tree(+Dir, -Tree) is det
Compute the content tree for a multi-file HTML document. We do this by processing Contents.html for making the toplevel tree that links to the individual files. Then we use html_content_tree/2 to materialize the trees for the files.
  523man_content_tree(Spec, node(manual, Chapters)) :-
  524    absolute_file_name(Spec, Dir,
  525                       [ file_type(directory),
  526                         access(read)
  527                       ]),
  528    directory_file_path(Dir, 'Contents.html', ContentsFile),
  529    load_html_file(ContentsFile, DOM),
  530    findall(Level-Path,
  531            ( xpath(DOM, //div(@class=Class), DIV),
  532              class_level(Class, Level),
  533              xpath(DIV, a(@class=sec,@href=File), _),
  534              \+ sub_atom(File, _, _, _, #),
  535              directory_file_path(Dir, File, Path)
  536            ),
  537            Pairs),
  538    index_chapters(Pairs, Chapters).
  539
  540class_level('toc-h1', 1).
  541class_level('toc-h2', 2).
  542class_level('toc-h3', 3).
  543class_level('toc-h4', 4).
  544
  545index_chapters([], []).
  546index_chapters([Level-File|T0], [node(Chapter, Children)|T]) :-
  547    html_content_tree(File, Node),
  548    Node = node(Chapter, Children0),
  549    append(Children0, Sections, Children),
  550    index_sections(T0, Level, Sections, T1),
  551    index_chapters(T1, T).
  552
  553index_sections([], _, [], []) :- !.
  554index_sections([SLevel-File|T0], Level, [Node|T], Rest) :-
  555    SLevel > Level,
  556    !,
  557    html_content_tree(File, Node),
  558    index_sections(T0, Level, T, Rest).
  559index_sections(Rest, _, [], Rest).
 man_packages_tree(-Tree) is det
Tree is the content tree of all packages
  566man_packages_tree(node(packages, Packages)) :-
  567    index_manual,
  568    Section = section(0, _, _, _),
  569    findall(File,
  570            man_index(Section, _Title, File, packages, _),
  571            Files),
  572    maplist(package_node, Files, Packages).
  573
  574package_node(File, Tree) :-
  575    html_content_tree(File, Tree).
 html_content_tree(+ManualFile, -Tree) is det
True when Tree represents the hierarchical structure of objects documented in the HTML file ManualFile. Tree is a term where of the form below. Object is a documentation object (typically a section or predicate indicator) that may be handed to object_link//1 and similar predicates to make a table of contents.
node(Object, ListOfTree).
  588html_content_tree(File, Tree) :-
  589    index_manual,
  590    findall(Offset-Obj,
  591            man_index(Obj, _Summary, File, _Class, Offset),
  592            Pairs),
  593    keysort(Pairs, Sorted),
  594    pairs_values(Sorted, Objects),
  595    make_tree(Objects, Trees),
  596    assertion(Trees = [_]),
  597    Trees = [Tree].
  598
  599make_tree([], []).
  600make_tree([Obj|T0], [node(Obj, Children)|T]) :-
  601    children(T0, Obj, Children, T1),
  602    make_tree(T1, T).
  603
  604children([], _, [], []) :- !.
  605children([Obj|T0], Root, [Node|T], Rest) :-
  606    section_level(Obj, ObjLevel),
  607    section_level(Root, Level),
  608    ObjLevel > Level,
  609    !,
  610    Node = node(Obj, Children),
  611    children(T0, Obj, Children, T1),
  612    children(T1, Root, T, Rest).
  613children([Obj|T0], Root, [Obj|T], Rest) :-
  614    \+ section_level(Obj, _),
  615    !,
  616    children(T0, Root, T, Rest).
  617children(Rest, _, [], Rest).
  618
  619section_level(section(Level, _Nr, _Id, _File), Level).
  620
  621
  622                 /*******************************
  623                 *            RETRIEVE          *
  624                 *******************************/
 load_man_object(+Obj, -Parent, -Path, -DOM) is nondet
load the desription of the object matching Obj from the HTML sources and return the DT/DD pair in DOM.
To be done
- Nondet?
  633load_man_object(Obj, ParentSection, Path, DOM) :-
  634    resolve_section(Obj, For),
  635    For = section(_,SN,_ID,Path),
  636    parent_section(For, ParentSection),
  637    findall(Nr-Pos, section_start(Path, Nr, Pos), Pairs),
  638    (   (   Pairs = [SN-_|_]
  639        ;   Pairs == []
  640        )
  641    ->  !,
  642        load_html_file(Path, DOM)           % Load whole file
  643    ;   append(_, [SN-Start|Rest], Pairs)
  644    ->  !,
  645        (   member(N-End, Rest),
  646            \+ sub_atom(N, 0, _, _, SN),
  647            Len is End - Start,
  648            Options = [content_length(Len)]
  649        ->  true
  650        ;   Options = []
  651        ),
  652        open(Path, read, In, [type(binary)]),
  653        seek(In, Start, bof, _),
  654        dtd(html, DTD),
  655        new_sgml_parser(Parser,
  656                        [ dtd(DTD)
  657                        ]),
  658        set_sgml_parser(Parser, file(Path)),
  659        set_sgml_parser(Parser, dialect(sgml)),
  660        set_sgml_parser(Parser, shorttag(false)),
  661        set_sgml_parser(Parser, defaults(false)),
  662        call_cleanup(sgml_parse(Parser,
  663                                [ document(DOM),
  664                                  source(In),
  665                                  syntax_errors(quiet)
  666                                | Options
  667                                ]),
  668                     ( free_sgml_parser(Parser),
  669                       close(In)
  670                     ))
  671    ).
  672load_man_object(For, Parent, Path, DOM) :-
  673    index_manual,
  674    object_spec(For, Obj),
  675    man_index(Obj, _, Path, _, Position),
  676    (   object_section(Path, Position, Parent)
  677    ->  true
  678    ;   Parent = Path
  679    ),
  680    open(Path, read, In, [type(binary)]),
  681    seek(In, Position, bof, _),
  682    dtd(html, DTD),
  683    new_sgml_parser(Parser,
  684                    [ dtd(DTD)
  685                    ]),
  686    set_sgml_parser(Parser, file(Path)),
  687    set_sgml_parser(Parser, dialect(sgml)),
  688    set_sgml_parser(Parser, shorttag(false)),
  689    set_sgml_parser(Parser, defaults(false)),
  690    call_cleanup(parse_dts_upto_dd(Parser, In, DOM),
  691                 ( free_sgml_parser(Parser),
  692                   close(In)
  693                 )).
  694
  695parse_dts_upto_dd(Parser, In, Description) :-
  696    sgml_parse(Parser,
  697               [ document(DOM0),
  698                 source(In),
  699                 parse(element),
  700                 syntax_errors(quiet)
  701               ]),
  702    (   DOM0 = [Element],
  703        Element = element(dt, _, _)
  704    ->  Description = [Element|More],
  705        parse_dts_upto_dd(Parser, In, More)
  706    ;   Description = DOM0
  707    ).
  708
  709section_start(Path, Nr, Pos) :-
  710    index_manual,
  711    man_index(section(_,Nr,_,_), _, Path, _, Pos).
 resolve_section(+SecIn, -SecOut) is det
Resolve symbolic path reference and fill in level and section number if this information is missing. The latter allows us to refer to files of the manual.
  719resolve_section(section(Level, No, Spec), Section) :-
  720    !,
  721    resolve_section(section(Level, No, _, Spec), Section).
  722resolve_section(section(Level, No, ID, Path),
  723                section(Level, No, ID, Path)) :-
  724    nonvar(ID),
  725    index_manual,
  726    man_index(section(Level,No,ID,Path), _, _, _, _),
  727    !.
  728resolve_section(section(Level, No, ID, Spec),
  729                section(Level, No, ID, Path)) :-
  730    ground(Spec),
  731    absolute_file_name(Spec, Path,
  732                       [ access(read)
  733                       ]),
  734    (   index_manual,
  735        man_index(section(Level, No, ID, Path), _, _, _, _)
  736    ->  true
  737    ;   path_allowed(Path)
  738    ->  true
  739    ;   permission_error(read, manual_file, Spec)
  740    ).
  741
  742
  743path_allowed(Path) :-                   % allow all files from swi/doc
  744    absolute_file_name(swi(doc), Parent,
  745                       [ access(read),
  746                         file_type(directory)
  747                       ]),
  748    sub_atom(Path, 0, _, _, Parent).
 parent_section(+Section, -Parent) is det
Parent is the parent-section of Section. First computes the section number and than finds the required number in the same file or same directory. If this doesn't exist, get the file as a whole.
  758parent_section(section(Level, Nr, _ID, File), Parent) :-
  759    integer(Level),
  760    Parent = section(PL, PNr, _PID, _PFile),
  761    PL is Level - 1,
  762    findall(B, sub_atom(Nr, B, _, _, '.'), BL),
  763    last(BL, Before),
  764    sub_atom(Nr, 0, Before, _, PNr),
  765    (   man_index(Parent, _, File, _, _)
  766    ->  true
  767    ;   man_index(Parent, _, ParentFile, _, _),
  768        same_dir(File, ParentFile)
  769    ->  true
  770    ;   man_index(Parent, _, _, _, _)
  771    ),
  772    !.
  773parent_section(section(Level, _, _, File), Parent) :-
  774    Parent = section(ParentLevel, _, _, File),
  775    man_index(Parent, _, _, _, _),
  776    ParentLevel < Level,
  777    !.
  778parent_section(section(_, _, _, File), File).
 object_section(+Path, +Position, -Section) is semidet
Section is the section in which object appears. This is the last section object before position.
  786object_section(Path, Pos, Section) :-
  787    Section = section(_,_,_,_),
  788    findall(Section,
  789           (man_index(Section, _, Path, _, SecPos), SecPos =< Pos),
  790            List),
  791    last(List, Section).
  792
  793same_dir(File1, File2) :-
  794    file_directory_name(File1, Dir),
  795    file_directory_name(File2, Dir).
 object_spec(+Atom, -SpecTerm)
Tranform the Name/Arity, etc strings as received from the HTTP into a term. Must return unique results.
  802object_spec(Spec, Spec).
  803object_spec(Atom, Spec) :-
  804    catch(atom_to_term(Atom, Spec, _), _, fail),
  805    !,
  806    Atom \== Spec.
  807object_spec(Atom, PI) :-
  808    name_to_object(Atom, PI).
  809
  810
  811                 /*******************************
  812                 *            EMIT              *
  813                 *******************************/
 man_page(+Obj, +Options)// is semidet
Produce a Prolog manual page for Obj. The page consists of a link to the section-file and a search field, followed by the predicate description. Obj is one of:

Options:

no_manual(Action)
If Action = fail, fail instead of displaying a not-found message.
links(Bool)
If true (default), include links to the parent object; if false, just emit the manual material.
  846man_page(Obj, Options) -->
  847    { ground(Obj),
  848      special_node(Obj)
  849    },
  850    !,
  851    html_requires(pldoc),
  852    man_links([], Options),
  853    man_matches([Obj], Obj, Options).
  854man_page(Obj0, Options) -->                     % Manual stuff
  855    { full_page(Obj0, Obj),
  856      findall((Parent+Path)-(Obj+DOM),
  857              load_man_object(Obj, Parent, Path, DOM),
  858              Matches),
  859      Matches = [_|_],
  860      !,
  861      pairs_keys(Matches, ParentPaths),
  862      Matches = [Parent+Path-_|_]
  863    },
  864    html_requires(pldoc),
  865    man_links(ParentPaths, Options),
  866    man_matches(Matches, Obj, Options).
  867man_page(Obj, Options) -->                      % PlDoc predicates, etc.
  868    { full_object(Obj, Full),
  869      findall(Full-File,
  870              ( doc_comment(Full, File:_, _, _),
  871                \+ private(Full, Options)
  872              ),
  873              Pairs),
  874      Pairs \== [],
  875      pairs_keys(Pairs, Objs)
  876    },
  877    !,
  878    html_requires(pldoc),
  879    (   { Pairs = [_-File] }
  880    ->  object_page_header(File, Options)
  881    ;   object_page_header(-, Options)
  882    ),
  883    objects(Objs, [ synopsis(true),
  884                    navtree(true)
  885                  | Options
  886                  ]).
  887man_page(Obj, Options) -->                      % failure
  888    { \+ option(no_manual(fail), Options)
  889    },
  890    html_requires(pldoc),
  891    man_links([], Options),
  892    html(p(class(noman),
  893           [ 'Sorry, No manual entry for ',
  894             b('~w'-[Obj])
  895           ])).
  896
  897%special_node(manual).          % redirected to the Introduction section
  898special_node(root).
  899special_node(packages).
  900
  901full_page(Obj, _) :-
  902    var(Obj), !, fail.
  903full_page(Obj, Obj) :-
  904    Obj = section(_,_,_,_),
  905    !.
  906full_page(section(ID), section(_,_,ID,_)) :- !.
  907full_page(manual, section(_,_,'sec:intro',_)) :- !.
  908full_page(Obj0, Obj) :-
  909    index_manual,
  910    ground(Obj0),
  911    alt_obj(Obj0, Obj),
  912    man_index(Obj, _, _, _, _),
  913    !.
  914full_page(Obj, Obj) :-
  915    ground(Obj).
  916
  917alt_obj(Obj, Obj).
  918alt_obj(Name/Arity, Name//DCGArity) :-
  919    integer(Arity),
  920    Arity >= 2,
  921    DCGArity is Arity - 2.
  922alt_obj(Name//DCGArity, Name/Arity) :-
  923    integer(DCGArity),
  924    Arity is DCGArity + 2.
 full_object(+Object, -Full) is semidet
Translate to canonical PlDoc object
  930full_object(Object, M:Obj) :-
  931    qualify(Object, M:Obj0),
  932    alt_obj(Obj0, Obj),
  933    doc_comment(M:Obj, _, _, _),
  934    !.
  935
  936qualify(M:O, M:O).
  937qualify(O, _:O).
 man_qualified_object(+Text, +Parent, -Object, -Section) is semidet
Get a qualified predicate description from Text that appears in the section Parent.

The tricky part is that there are cases where multiple modules export the same predicate. We must find from the title of the manual section which library is documented.

  949man_qualified_object(Text, Parent, Object, Section) :-
  950    atom(Text),
  951    atom_pi(Text, PI),
  952    ground(PI),
  953    !,
  954    man_qualified_object_2(PI, Parent, Object, Section).
  955man_qualified_object(Object0, Parent, Object, Section) :-
  956    man_qualified_object_2(Object0, Parent, Object, Section).
  957
  958man_qualified_object_2(Name/Arity, Parent, Module:Name/Arity, Section) :-
  959    object_module(Parent, Module, Section),
  960    !.
  961man_qualified_object_2(Object, Parent, Object, Parent).
 man_synopsis(+Object, +Section)//
Give synopsis details for a fully specified predicate indicator and link this to the section.
  969:- public
  970    man_synopsis//2.                % called from man_match//2
  971
  972man_synopsis(PI, Section) -->
  973    { object_href(Section, HREF)
  974    },
  975    object_synopsis(PI, [href(HREF)]).
 object_module(+Section0, -Module, -Section) is semidet
Find the module documented by Section.
To be done
- This requires that the documented file is loaded. If not, should we use the title of the section?
  984object_module(Section0, Module, Section) :-
  985    parent_section_ndet(Section0, Section),
  986    man_index(Section, Title, _File, _Class, _Offset),
  987    (   once(sub_atom(Title, B, _, _, :)),
  988        sub_atom(Title, 0, B, _, Atom),
  989        catch(term_to_atom(Term, Atom), _, fail),
  990        ground(Term),
  991        Term = library(_)
  992    ->  !,
  993        absolute_file_name(Term, PlFile,
  994                           [ file_type(prolog),
  995                             access(read),
  996                             file_errors(fail)
  997                           ]),
  998        module_property(Module, file(PlFile))
  999    ).
 1000
 1001parent_section_ndet(Section, Section).
 1002parent_section_ndet(Section, Parent) :-
 1003    parent_section(Section, Parent0),
 1004    parent_section_ndet(Parent0, Parent).
 1005
 1006
 1007man_matches(Matches, Object, Options) -->
 1008    { option(navtree(false), Options) },
 1009    !,
 1010    man_matches_nt(Matches, Object, Options).
 1011man_matches(Matches, Object, Options) -->
 1012    html([ div(class(navtree),
 1013               div(class(navwindow),
 1014                   \man_nav_tree(Object, Options))),
 1015           div(class(navcontent),
 1016               \man_matches_nt(Matches, Object, Options))
 1017         ]).
 1018
 1019
 1020man_matches_nt([Match], Object, Options) -->
 1021    { option(footer(true), Options, true) },
 1022    !,
 1023    man_match(Match, Object),
 1024    object_page_footer(Object, []).
 1025man_matches_nt(Matches, Object, _) -->
 1026    man_matches_list(Matches, Object).
 1027
 1028man_matches_list([], _) --> [].
 1029man_matches_list([H|T], Obj) --> man_match(H, Obj), man_matches_list(T, Obj).
 man_match(+Term, +Object)//
If possible, insert the synopsis into the title of the description.
 1036man_match(packages, packages) -->
 1037    !,
 1038    html({|html||
 1039              <p>
 1040              Packages are relatively independent add-on libraries that
 1041              may not be available in all installations.
 1042             |}).
 1043man_match(root, root) -->
 1044    !,
 1045    man_overview([]).
 1046man_match((Parent+Path)-(Obj+[element(dt,A,C0)|DD]), Obj) -->
 1047    { man_qualified_object(Obj, Parent, QObj, Section),
 1048      !,
 1049      C = [ span(style('float:right;margin-left:5px;'),
 1050                 \object_source_button(QObj, [link_source(true)]))
 1051          | C0
 1052          ]
 1053    },
 1054    dom_list([ element(dt,[],[\man_synopsis(QObj, Section)]),
 1055               element(dt,A,C)
 1056             | DD
 1057             ], Path).
 1058man_match((_Parent+Path)-(Obj+DOM), Obj) -->
 1059    dom_list(DOM, Path).
 1060
 1061
 1062:- html_meta
 1063    dom_list(html, +, ?, ?). 1064
 1065dom_list(_:[], _) -->
 1066    !,
 1067    [].
 1068dom_list(M:[H|T], Path) -->
 1069    dom(H, Path),
 1070    dom_list(M:T, Path).
 1071
 1072dom(element(E, Atts, Content), Path) -->
 1073    !,
 1074    dom_element(E, Atts, Content, Path).
 1075dom(CDATA, _) -->
 1076    html(CDATA).
 1077
 1078dom_element(a, _, [], _) -->                   % Useless back-references
 1079    !,
 1080    [].
 1081dom_element(a, Att, Content, Path) -->
 1082    { memberchk(href=HREF, Att),
 1083      (   memberchk(class=Class, Att)
 1084      ->  true
 1085      ;   Class = unknown
 1086      ),
 1087      rewrite_ref(Class, HREF, Path, Myref)
 1088    },
 1089    !,
 1090    html(a(href(Myref), \dom_list(Content, Path))).
 1091dom_element(span, Att, [CDATA], _) -->
 1092    { memberchk(class='pred-ext', Att),
 1093      atom_pi(CDATA, PI),
 1094      documented(PI),
 1095      http_link_to_id(pldoc_man, [predicate=CDATA], HREF)
 1096    },
 1097    !,
 1098    html(a(href(HREF), CDATA)).
 1099dom_element(img, Att0, [], Path) -->
 1100    { selectchk(src=Src, Att0, Att1),
 1101      current_prolog_flag(home, SWI),
 1102      sub_atom(Path, 0, Len, _, SWI),
 1103      (   sub_atom(Path, Len, _, _, '/doc/Manual/')
 1104      ->  Handler = manual_file
 1105      ;   sub_atom(Path, Len, _, _, '/doc/packages/')
 1106      ->  Handler = pldoc_package
 1107      ),
 1108      !,
 1109      http_link_to_id(Handler, [], ManRef),
 1110      directory_file_path(ManRef, Src, NewPath),
 1111      Begin =.. [img, src(NewPath) | Att1]
 1112    },
 1113    !,
 1114    html_begin(Begin),
 1115    html_end(img).
 1116dom_element(div, Att, _, _) -->
 1117    { memberchk(class=navigate, Att) },
 1118    !.
 1119dom_element(html, _, Content, Path) -->        % do not emit a html for the second time
 1120    !,
 1121    dom_list(Content, Path).
 1122dom_element(head, _, Content, Path) -->        % do not emit a head for the second time
 1123    !,
 1124    dom_list(Content, Path).
 1125dom_element(title, _, _, _) --> !.
 1126dom_element(link, _, _, _) --> !.
 1127dom_element(body, _, Content, Path) -->        % do not emit a body for the second time
 1128    !,
 1129    dom_list(Content, Path).
 1130dom_element(Name, Attrs, Content, Path) -->
 1131    { Begin =.. [Name|Attrs] },
 1132    html_begin(Begin),
 1133    dom_list(Content, Path),
 1134    html_end(Name).
 documented(+PI) is semidet
True if we have documentation about PI
 1140documented(PI) :-
 1141    index_manual,
 1142    man_index(PI, _, _, _, _),
 1143    !.
 1144documented(PI) :-
 1145    full_object(PI, _Obj).
 rewrite_ref(+Class, +Ref0, +Path, -ManRef) is semidet
Rewrite Ref0 from the HTML reference manual format to the server format. Reformatted:
File#Name/Arity
Local reference using the manual presentation /man?predicate=PI.
File#sec:NR
Rewrite to section(Level, NT, ID, FilePath)
File#flag:Name
Rewrite to section(Level, NT, ID, FilePath)#flag:Name

$ File#Name() Rewrite to /man/CAPI=Name

Arguments:
Class- Class of the <A>. Supported classes are
secLink to a section
predLink to a predicate
flaglink to a Prolog flag
Ref0- Initial reference from the a element
Path- Currently loaded file
ManRef- PlDoc server reference
 1175rewrite_ref(pred, Ref0, _, Ref) :-              % Predicate/DCG reference
 1176    sub_atom(Ref0, _, _, A, '#'),
 1177    !,
 1178    sub_atom(Ref0, _, A, 0, Fragment),
 1179    name_to_object(Fragment, PI),
 1180    man_index(PI, _, _, _, _),
 1181    uri_encoded(query_value, Fragment, Enc),
 1182    http_location_by_id(pldoc_man, ManHandler),
 1183    format(string(Ref), '~w?predicate=~w', [ManHandler, Enc]).
 1184rewrite_ref(function, Ref0, _, Ref) :-          % Arithmetic function reference
 1185    sub_atom(Ref0, _, _, A, '#'),
 1186    !,
 1187    sub_atom(Ref0, _, A, 0, Fragment),
 1188    name_to_object(Fragment, PI),
 1189    man_index(PI, _, _, _, _),
 1190    PI=f(Name/Arity),
 1191    format(atom(PIName), '~w/~w', [Name,Arity]),
 1192    uri_encoded(query_value, PIName, Enc),
 1193    http_location_by_id(pldoc_man, ManHandler),
 1194    format(string(Ref), '~w?function=~w', [ManHandler, Enc]).
 1195rewrite_ref(func, Ref0, _, Ref) :-              % C-API reference
 1196    sub_atom(Ref0, _, _, A, '#'),
 1197    !,
 1198    sub_atom(Ref0, _, A, 0, Fragment),
 1199    name_to_object(Fragment, Obj),
 1200    man_index(Obj, _, _, _, _),
 1201    Obj = c(Function),
 1202    uri_encoded(query_value, Function, Enc),
 1203    http_location_by_id(pldoc_man, ManHandler),
 1204    format(string(Ref), '~w?CAPI=~w', [ManHandler, Enc]).
 1205rewrite_ref(sec, Ref0, Path, Ref) :-            % Section inside a file
 1206    sub_atom(Ref0, B, _, A, '#'),
 1207    !,
 1208    sub_atom(Ref0, _, A, 0, Fragment),
 1209    sub_atom(Ref0, 0, B, _, File),
 1210    referenced_section(Fragment, File, Path, Section),
 1211    object_href(Section, Ref).
 1212rewrite_ref(sec, File, Path, Ref) :-            % Section is a file
 1213    file_directory_name(Path, Dir),
 1214    atomic_list_concat([Dir, /, File], SecPath),
 1215    Obj = section(_, _, _, SecPath),
 1216    man_index(Obj, _, _, _, _),
 1217    !,
 1218    object_href(Obj, Ref).
 1219rewrite_ref(cite, Ref0, Path, Ref) :-           % Citation (bit hard-wired)
 1220    debug(pldoc(cite), 'Cite ref ~q ~q', [Ref0, Path]),
 1221    sub_atom(Ref0, _, _, A, '#'),
 1222    !,
 1223    sub_atom(Ref0, _, A, 0, Fragment),
 1224    uri_encoded(query_value, Fragment, Enc),
 1225    http_location_by_id(pldoc_man, ManHandler),
 1226    format(string(Ref), '~w?section=bibliography#~w', [ManHandler, Enc]).
 1227rewrite_ref(flag, Ref0, Path, Ref) :-
 1228    sub_atom(Ref0, B, _, A, '#'),
 1229    !,
 1230    sub_atom(Ref0, 0, B, _, File),
 1231    sub_atom(Ref0, _, A, 0, Fragment),
 1232    file_directory_name(Path, Dir),
 1233    atomic_list_concat([Dir, /, File], SecPath),
 1234    Obj = section(_, _, _, SecPath),
 1235    man_index(Obj, _, _, _, _),
 1236    !,
 1237    object_href(Obj, Ref1),
 1238    format(string(Ref), '~w#~w', [Ref1, Fragment]).
 name_to_object(+Atom, -PredicateIndicator) is semidet
If Atom is `Name/Arity', decompose to Name and Arity. No errors.
 1244name_to_object(Atom, Object) :-
 1245    atom(Atom),
 1246    atom_pi(Atom, PI),
 1247    ground(PI),
 1248    (   PI = Name/Arity,
 1249        integer(Arity),
 1250        atom_concat('f-', FuncName, Name)
 1251    ->  Object = f(FuncName/Arity)
 1252    ;   Object = PI
 1253    ).
 1254name_to_object(Atom, c(Function)) :-
 1255    atom(Atom),
 1256    sub_atom(Atom, 0, _, _, 'PL_'),
 1257    sub_atom(Atom, B, _, _, '('),
 1258    !,
 1259    sub_atom(Atom, 0, B, _, Function).
 referenced_section(+Fragment, +File, +Path, -Section)
 1264referenced_section(Fragment, File, Path, section(Level, Nr, ID, SecPath)) :-
 1265    atom_concat('sec:', Nr, Fragment),
 1266    (   File == ''
 1267    ->  SecPath = Path
 1268    ;   file_directory_name(Path, Dir),
 1269        atomic_list_concat([Dir, /, File], SecPath)
 1270    ),
 1271    man_index(section(Level, Nr, ID, SecPath), _, _, _, _).
 man_links(+ParentPaths, +Options)// is det
Create top link structure for manual pages.
 1278man_links(ParentPaths, Options) -->
 1279    prolog:doc_page_header(parents(ParentPaths), Options),
 1280    !.
 1281man_links(ParentPaths, Options) -->
 1282    { option(links(true), Options, true),
 1283      option(header(true), Options, true)
 1284    },
 1285    !,
 1286    html([ div(class(navhdr),
 1287               [ div(class(jump), \man_parent(ParentPaths)),
 1288                 div(class(search), \search_form(Options)),
 1289                 br(clear(right))
 1290               ]),
 1291           p([])
 1292         ]).
 1293man_links(_, _) -->
 1294    [].
 1295
 1296man_parent(ParentPaths) -->
 1297    { maplist(parent_to_section, ParentPaths, [Section|MoreSections]),
 1298      maplist(=(Section), MoreSections)
 1299    },
 1300    !,
 1301    object_ref(Section, [secref_style(number_title)]).
 1302man_parent(_) --> [].
 1303
 1304parent_to_section(X+_, X) :-
 1305    X = section(_,_,_,_),
 1306    !.
 1307parent_to_section(File+_, Section) :-
 1308    atom(File),
 1309    man_index(Section, _Title, File, _Class, _Offset),
 1310    !.
 section_link(+Obj, +Options)// is det
Create link to a section. Options recognised:
secref_style(+Style)
One of number, title or number_title.
 1319section_link(Section, Options) -->
 1320    { option(secref_style(Style), Options, number)
 1321    },
 1322    section_link(Style, Section, Options).
 1323
 1324section_link(number, section(_, Number, _, _), _Options) -->
 1325    !,
 1326    (   {Number == '0'}             % Title.  Package?
 1327    ->  []
 1328    ;   html(['Sec. ', Number])
 1329    ).
 1330section_link(title, Obj, _Options) -->
 1331    !,
 1332    { man_index(Obj, Title, _File, _Class, _Offset)
 1333    },
 1334    html(Title).
 1335section_link(_, Obj, _Options) -->
 1336    !,
 1337    { Obj = section(_, Number, _, _),
 1338      man_index(Obj, Title, _File, _Class, _Offset)
 1339    },
 1340    (   { Number == '0' }
 1341    ->  html(Title)
 1342    ;   html([Number, ' ', Title])
 1343    ).
 function_link(+Function, +Options) is det
Create a link to a C-function
 1349function_link(Function, _) -->
 1350    html([Function, '()']).
 1351
 1352
 1353                 /*******************************
 1354                 *       INDICES & OVERVIEW     *
 1355                 *******************************/
 man_overview(+Options)// is det
Provide a toplevel overview on the manual: the reference manual and the available packages.
 1362man_overview(Options) -->
 1363    { http_absolute_location(pldoc_man(.), RefMan, [])
 1364    },
 1365    html([ h1('SWI-Prolog documentation'),
 1366           blockquote(class(refman_link),
 1367                      a(href(RefMan),
 1368                        'SWI-Prolog reference manual')),
 1369           \package_overview(Options),
 1370           \paperback(Options)
 1371         ]).
 1372
 1373package_overview(Options) -->
 1374    html([ h2(class(package_doc_title),
 1375              'SWI-Prolog package documentation'),
 1376           blockquote(class(package_overview),
 1377                      \packages(Options))
 1378         ]).
 1379
 1380packages(Options) -->
 1381    { findall(Pkg, current_package(Pkg), Pkgs)
 1382    },
 1383    packages(Pkgs, Options).
 1384
 1385packages([], _) -->
 1386    [].
 1387packages([Pkg|T], Options) -->
 1388    package(Pkg, Options),
 1389    packages(T, Options).
 1390
 1391package(pkg(Title, HREF, HavePackage), Options) -->
 1392    { package_class(HavePackage, Class, Options)
 1393    },
 1394    html(div(class(Class),
 1395             a([href(HREF)], Title))).
 1396
 1397package_class(true,  pkg_link, _).
 1398package_class(false, no_pkg_link, _).
 1399
 1400current_package(pkg(Title, HREF, HavePackage)) :-
 1401    man_index(section(0, _, _, _), Title, File, packages, _),
 1402    file_base_name(File, FileNoDir),
 1403    file_name_extension(Base, _, FileNoDir),
 1404    (   exists_source(library(Base))
 1405    ->  HavePackage = true
 1406    ;   HavePackage = false
 1407    ),
 1408    http_absolute_location(pldoc_pkg(FileNoDir), HREF, []).
 1409
 1410
 1411:- http_handler(pldoc(jpl),      pldoc_jpl,              [prefix]). 1412:- http_handler(pldoc_pkg(.),    pldoc_package,          [prefix]). 1413:- http_handler(pldoc_man(.),    pldoc_refman,           [prefix]). 1414:- http_handler(pldoc(packages), pldoc_package_overview, []).
 pldoc_jpl(+Request)
Hack to include JPL documentation in server.
 1420pldoc_jpl(Request) :-
 1421    memberchk(path_info(JPLFile), Request),
 1422    atom_concat('doc/packages/jpl', JPLFile, Path),
 1423    http_reply_file(swi(Path), [], Request).
 pldoc_package(+Request)
HTTP handler for PlDoc package documentation. Accepts /pldoc/package/<package>.{html,gif}. The path =/pldoc/package/<package>= is redirected to the canonical object version.
 1432pldoc_package(Request) :-
 1433    (   \+ option(path_info(_), Request)
 1434    ->  true
 1435    ;   option(path_info(/), Request)
 1436    ),
 1437    http_link_to_id(pldoc_object, [object=packages], HREF),
 1438    http_redirect(see_other, HREF, Request).
 1439pldoc_package(Request) :-
 1440    memberchk(path_info(Img), Request),
 1441    file_mime_type(Img, image/_),
 1442    !,
 1443    atom_concat('doc/packages/', Img, Path),
 1444    http_reply_file(swi(Path), [], Request).
 1445pldoc_package(Request) :-
 1446    memberchk(path_info('jpl'), Request),
 1447    !,
 1448    memberchk(path(Path0), Request),
 1449    atom_concat(Path0, /, Path),
 1450    http_redirect(moved, Path, Request).
 1451pldoc_package(Request) :-
 1452    memberchk(path_info(JPLFile), Request),
 1453    (   JPLFile == 'jpl/'
 1454    ->  Path = 'doc/packages/jpl/index.html'
 1455    ;   sub_atom(JPLFile, 0, _, _, 'jpl/')
 1456    ->  atom_concat('doc/packages/', JPLFile, Path)
 1457    ),
 1458    http_reply_file(swi(Path), [], Request).
 1459pldoc_package(Request) :-
 1460    memberchk(path_info(PkgDoc), Request),
 1461    ensure_html_ext(PkgDoc, PkgHtml),
 1462    atom_concat('packages/', PkgHtml, Path),
 1463    term_to_atom(section(Path), Object),
 1464    http_link_to_id(pldoc_object, [object=Object], HREF),
 1465    http_redirect(see_other, HREF, Request).
 1466
 1467ensure_html_ext(Pkg, PkgHtml) :-
 1468    file_name_extension(_, html, Pkg),
 1469    !,
 1470    PkgHtml = Pkg.
 1471ensure_html_ext(Pkg, PkgHtml) :-
 1472    file_name_extension(Pkg, html, PkgHtml).
 pldoc_package_overview(+Request)
Provide an overview of the package documentation
 1478pldoc_package_overview(_Request) :-
 1479    reply_html_page(
 1480        pldoc(packages),
 1481        title('SWI-Prolog package documentation'),
 1482        \package_overview([])).
 paperback(+Options)//
Link to the paperback version of the manual.
 1488paperback(_Options) -->
 1489    { expand_url_path(swipl_book(.), HREF)
 1490    },
 1491    html([ h2('The manual as a book'),
 1492           p([ 'A paperback version of the manual is ',
 1493               a(href(HREF), 'available'), '.'
 1494             ])
 1495         ]).
 pldoc_refman(+Request)
HTTP handler for PlDoc Reference Manual access. Accepts /refman/[<package>.html.]
 1502pldoc_refman(Request) :-
 1503    memberchk(path_info(Section), Request),
 1504    \+ sub_atom(Section, _, _, _, /),
 1505    Obj = section(0,_,_,_),
 1506    index_manual,
 1507    man_index(Obj, Title, File, manual, _),
 1508    file_base_name(File, Section),
 1509    !,
 1510    reply_html_page(pldoc(man),
 1511                    title(Title),
 1512                    \object_page(Obj, [])).
 1513pldoc_refman(Request) :-                % server Contents.html
 1514    \+ memberchk(path_info(_), Request),
 1515    !,
 1516    http_link_to_id(pldoc_object, [object(manual)], HREF),
 1517    http_redirect(see_other, HREF, Request).
 1518pldoc_refman(Request) :-
 1519    memberchk(path(Path), Request),
 1520    existence_error(http_location, Path).
 1521
 1522
 1523                 /*******************************
 1524                 *          HOOK SEARCH         *
 1525                 *******************************/
 1526
 1527prolog:doc_object_summary(section(ID), Class, File, Summary) :-
 1528    nonvar(ID),                     % when generating, only do full ones
 1529    index_manual,
 1530    man_index(section(_Level, _No, ID, _Path), Summary, File, Class, _Offset).
 1531prolog:doc_object_summary(Obj, Class, File, Summary) :-
 1532    index_manual,
 1533    man_index(Obj, Summary, File, Class, _Offset).
 1534
 1535prolog:doc_object_page(Obj, Options) -->
 1536    man_page(Obj, [no_manual(fail),footer(false)|Options]).
 prolog:doc_object_link(+Obj, +Options)//
Provide the HTML to describe Obj for linking purposes.
 1542prolog:doc_object_link(Obj, Options) -->
 1543    { Obj = section(_,_,_,_),
 1544      index_manual
 1545    },
 1546    !,
 1547    section_link(Obj, Options).
 1548prolog:doc_object_link(Obj0, Options) -->
 1549    { Obj0 = section(ID),
 1550      Obj = section(_Level, _No, ID, _Path),
 1551      index_manual,
 1552      man_index(Obj, _, _, _, _)
 1553    },
 1554    !,
 1555    section_link(Obj, Options).
 1556prolog:doc_object_link(Obj, Options) -->
 1557    { Obj = c(Function) },
 1558    !,
 1559    function_link(Function, Options).
 1560prolog:doc_object_link(root, _) -->
 1561    !,
 1562    html('Documentation').
 1563prolog:doc_object_link(manual, _Options) -->
 1564    !,
 1565    html('Reference manual').
 1566prolog:doc_object_link(packages, _) -->
 1567    html('Packages').
 1568
 1569prolog:doc_category(manual,   30, 'SWI-Prolog Reference Manual').
 1570prolog:doc_category(packages, 40, 'Package documentation').
 1571
 1572prolog:doc_file_index_header(File, Options) -->
 1573    { Section = section(_Level, _No, _ID, File),
 1574      man_index(Section, _Summary, File, _Cat, _Offset)
 1575    },
 1576    !,
 1577    html(tr(th([colspan(3), class(section)],
 1578               [ \object_ref(Section,
 1579                             [ secref_style(number_title)
 1580                             | Options
 1581                             ])
 1582               ]))).
 1583
 1584prolog:doc_object_title(Obj, Title) :-
 1585    Obj = section(_,_,_,_),
 1586    man_index(Obj, Title, _, _, _),
 1587    !.
 1588
 1589prolog:doc_canonical_object(section(_Level, _No, ID, _Path),
 1590                            section(ID)).
 1591
 1592swi_local_path(Path, Local) :-
 1593    atom(Path),
 1594    is_absolute_file_name(Path),
 1595    absolute_file_name(swi(doc), SWI,
 1596                       [ file_type(directory),
 1597                         solutions(all)
 1598                       ]),
 1599    directory_file_path(SWI, Local, Path),
 1600    !.
 prolog:doc_object_href(+Object, -HREF) is semidet
Produce a HREF for section objects.
 1606prolog:doc_object_href(section(ID), HREF) :-
 1607    nonvar(ID),
 1608    atom_concat('sec:', Sec, ID),
 1609    http_link_to_id(pldoc_man, [section(Sec)], HREF).
 1610prolog:doc_object_href(section(_Level, _No, ID, _Path), HREF) :-
 1611    nonvar(ID),
 1612    atom_concat('sec:', Sec, ID),
 1613    http_link_to_id(pldoc_man, [section(Sec)], HREF).
 1614
 1615
 1616                 /*******************************
 1617                 *           MESSAGES           *
 1618                 *******************************/
 1619
 1620:- multifile prolog:message//1. 1621
 1622prolog:message(pldoc(no_section_id(File, Title))) -->
 1623    [ 'PlDoc: ~w: no id for section "~w"'-[File, Title] ].
 1624prolog:message(pldoc(duplicate_ids(L))) -->
 1625    [ 'PlDoc: duplicate manual section IDs:'-[], nl
 1626    ],
 1627    duplicate_ids(L).
 1628
 1629duplicate_ids([]) --> [].
 1630duplicate_ids([H|T]) --> duplicate_id(H), duplicate_ids(T).
 1631
 1632duplicate_id(Id) -->
 1633    { findall(File, man_index(section(_,_,Id,File),_,_,_,_), Files) },
 1634    [ '    ~w: ~p'-[Id, Files], nl ]