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-2015, 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).
  67
  68/** <module> Process SWI-Prolog HTML manuals
  69
  70*/
  71
  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
  90
  91%!  clean_man_index is det.
  92%
  93%   Clean already loaded manual index.
  94
  95clean_man_index :-
  96    retractall(man_index(_,_,_,_,_)).
  97
  98
  99%!  manual_directory(-Class, -Dir)// is nondet.
 100%
 101%   True if Dir is a directory holding manual files. Class is an
 102%   identifier used by doc_object_summary/4.
 103
 104manual_directory(manual,   swi('doc/Manual')).
 105manual_directory(packages, swi('doc/packages')).
 106
 107
 108                 /*******************************
 109                 *          PARSE MANUAL        *
 110                 *******************************/
 111
 112%!  index_manual is det.
 113%
 114%   Load the manual index if not already done.
 115
 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).
 156
 157
 158%!  index_man_directory(Dir, +Options) is det
 159%
 160%   Index  the  HTML  directory   Dir.    Options are:
 161%
 162%           * class(Class)
 163%           Define category of the found objects.
 164%
 165%   Remaining Options are passed to absolute_file_name/3.
 166
 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).
 177
 178
 179%!  index_man_file(+Class, +File)
 180%
 181%   Collect the documented objects from the SWI-Prolog manual file
 182%   File.
 183
 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                 )).
 205
 206
 207%!  index_on_begin(+Element, +Attributes, +Parser) is semidet.
 208%
 209%   Called from sgml_parse/2 in  index_man_file/2.   Element  is the
 210%   name of the element, Attributes the  list of Name=Value pairs of
 211%   the open attributes. Parser is the parser objects.
 212
 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    nb_setval(pldoc_man_index, [dd(PI, File, Offset)|DD0]).
 230index_on_begin(dd, _, Parser) :-
 231    !,
 232    nb_getval(pldoc_man_index, DDList0), DDList0 \== [],
 233    nb_setval(pldoc_man_index, []),
 234    sgml_parse(Parser,
 235               [ document(DD),
 236                 syntax_errors(quiet),
 237                 parse(content)
 238               ]),
 239    summary(DD, Summary),
 240    nb_getval(pldoc_index_class, Class),
 241    reverse(DDList0, [dd(Object, File, Offset)|DDTail]),
 242    assertz(man_index(Object, Summary, File, Class, Offset)),
 243    forall(member(dd(Obj2,_,_), DDTail),
 244           assertz(man_index(Obj2, Summary, File, Class, Offset))).
 245index_on_begin(div, Attributes, Parser) :-
 246    !,
 247    memberchk(class=title, Attributes),
 248    get_sgml_parser(Parser, charpos(Offset)),
 249    get_sgml_parser(Parser, file(File)),
 250    sgml_parse(Parser,
 251               [ document(DOM),
 252                 syntax_errors(quiet),
 253                 parse(content)
 254               ]),
 255    dom_to_text(DOM, Title),
 256    nb_getval(pldoc_index_class, Class),
 257    swi_local_path(File, Local),
 258    assertz(man_index(section(0, '0', Local, File),
 259                      Title, File, Class, Offset)).
 260index_on_begin(H, Attributes, Parser) :- % TBD: add class for document title.
 261    heading(H, Level),
 262    get_sgml_parser(Parser, charpos(Offset)),
 263    get_sgml_parser(Parser, file(File)),
 264    sgml_parse(Parser,
 265               [ document(Doc),
 266                 syntax_errors(quiet),
 267                 parse(content)
 268               ]),
 269    dom_section(Doc, Nr, Title),
 270    nb_getval(pldoc_index_class, Class),
 271    section_id(Attributes, Title, File, ID),
 272    assertz(man_index(section(Level, Nr, ID, File),
 273                      Title, File, Class, Offset)).
 274
 275section_id(Attributes, _Title, _, ID) :-
 276    memberchk(id=ID, Attributes),
 277    !.
 278section_id(_, "Bibliography", _, 'sec:bibliography') :- !.
 279section_id(_Attributes, Title, File, ID) :-
 280    atomic_list_concat(Words, ' ', Title),
 281    atomic_list_concat(Words, '_', ID0),
 282    atom_concat('sec:', ID0, ID),
 283    print_message(warning, pldoc(no_section_id(File, Title))).
 284
 285%!  dom_section(+HeaderDOM, -NR, -Title) is semidet.
 286%
 287%   NR is the section number (e.g. 1.1, 1.23) and Title is the title
 288%   from a section header. The  first   clauses  processes the style
 289%   information from latex2html, emitting sections as:
 290%
 291%   ==
 292%   <HN> <A name="sec:nr"><span class='sec-nr'>NR</span>|_|
 293%                         <span class='sec-title'>Title</span>
 294%   ==
 295
 296dom_section(DOM, Nr, Title) :-
 297    sub_term([ element(span, A1, [Nr]) | Rest ], DOM),
 298    append(_Sep, [element(span, A2, TitleDOM)], Rest),
 299    memberchk(class='sec-nr', A1),
 300    memberchk(class='sec-title', A2),
 301    !,
 302    dom_to_text(TitleDOM, Title).
 303dom_section(DOM, Nr, Title) :-
 304    dom_to_text(DOM, Title),
 305    section_number(Title, Nr, Title).
 306
 307section_number(Title, Nr, PlainTitle) :-
 308    sub_atom(Title, 0, 1, _, Start),
 309    (   char_type(Start, digit)
 310    ->  true
 311    ;   char_type(Start, upper),
 312        sub_atom(Title, 1, 1, _, '.')       % A., etc: Appendices
 313    ),
 314    sub_atom(Title, B, _, A, ' '),
 315    !,
 316    sub_atom(Title, 0, B, _, Nr),
 317    sub_string(Title, _, A, 0, PlainTitle).
 318
 319heading(h1, 1).
 320heading(h2, 2).
 321heading(h3, 3).
 322heading(h4, 4).
 323
 324
 325%!  summary(+DOM, -Summary:string) is det.
 326%
 327%   Summary is the first sentence of DOM.
 328
 329summary(DOM, Summary) :-
 330    phrase(summary(DOM, _), SummaryCodes0),
 331    phrase(normalise_white_space(SummaryCodes), SummaryCodes0),
 332    string_codes(Summary, SummaryCodes).
 333
 334summary([], _) -->
 335    !,
 336    [].
 337summary(_, Done) -->
 338    { Done == true },
 339    !,
 340    [].
 341summary([element(_,_,Content)|T], Done) -->
 342    !,
 343    summary(Content, Done),
 344    summary(T, Done).
 345summary([CDATA|T], Done) -->
 346    { atom_codes(CDATA, Codes)
 347    },
 348    (   { Codes = [Period|Rest],
 349          code_type(Period, period),
 350          space(Rest)
 351        }
 352    ->  [ Period ],
 353        { Done = true }
 354    ;   { append(Sentence, [C, Period|Rest], Codes),
 355          code_type(Period, period),
 356          \+ code_type(C, period),
 357          space(Rest)
 358        }
 359    ->  string(Sentence),
 360        [C, Period],
 361        { Done = true }
 362    ;   string(Codes),
 363        summary(T, Done)
 364    ).
 365
 366string([]) -->
 367    [].
 368string([H|T]) -->
 369    [H],
 370    string(T).
 371
 372space([C|_]) :- code_type(C, space), !.
 373space([]).
 374
 375%!  dom_to_text(+DOM, -Text)
 376%
 377%   Extract the text of a parsed HTML term.  White-space in the
 378%   result is normalised.  See normalise_white_space//1.
 379
 380dom_to_text(Dom, Text) :-
 381    phrase(cdata_list(Dom), CDATA),
 382    with_output_to(codes(Codes0),
 383                   forall(member(T, CDATA),
 384                          write(T))),
 385    phrase(normalise_white_space(Codes), Codes0),
 386    string_codes(Text, Codes).
 387
 388cdata_list([]) -->
 389    [].
 390cdata_list([H|T]) -->
 391    cdata(H),
 392    cdata_list(T).
 393
 394cdata(element(_, _, Content)) -->
 395    !,
 396    cdata_list(Content).
 397cdata(CDATA) -->
 398    { atom(CDATA) },
 399    !,
 400    [CDATA].
 401cdata(_) -->
 402    [].
 403
 404%!  current_man_object(?Object) is nondet.
 405
 406current_man_object(Object) :-
 407    index_manual,
 408    man_index(Object, _, _, _, _).
 409
 410
 411                 /*******************************
 412                 *           HIERARCHY          *
 413                 *******************************/
 414
 415%!  man_nav_tree(+Obj, +Options) is semidet.
 416%
 417%   Create a navigation tree consisting of   a nested =ul= list that
 418%   reflects the location of Obj in the manual.
 419
 420man_nav_tree(Obj, Options) -->
 421    { ensure_man_tree,
 422      man_nav_tree(Obj, Tree, Options),
 423      TreeOptions = [ secref_style(title)
 424                    | Options
 425                    ]
 426    },
 427    html(ul(class(nav),
 428            \object_tree(Tree, [Obj], TreeOptions))).
 429
 430
 431%!  man_nav_tree(+Obj, -Tree, +Options) is semidet.
 432%
 433%   True when Tree is the navigation tree  for Obj. By default, this
 434%   is the tree going from  the  leaf   to  the  root, unfolding the
 435%   neighbors of Obj.
 436
 437man_nav_tree(Obj, Tree, _Options) :-
 438    man_child_of(Obj, Parent),
 439    !,
 440    findall(Neighbour, man_child_of(Neighbour, Parent), Neighbours0),
 441    (   findall(Child, man_child_of(Child, Obj), Children),
 442        Children \== []
 443    ->  select(Obj, Neighbours0, node(Obj, Children), Neighbours)
 444    ;   Neighbours = Neighbours0
 445    ),
 446    path_up(node(Parent, Neighbours), Tree).
 447man_nav_tree(Obj, node(Obj, Children), _Options) :-
 448    findall(Child, man_child_of(Child, Obj), Children).
 449
 450
 451path_up(Node, Tree) :-
 452    node_id(Node, Id),
 453    man_child_of(Id, Parent),
 454    !,
 455    (   Parent == root
 456    ->  findall(Neighbour, man_child_of(Neighbour, Parent), Neighbours0),
 457        select(Id, Neighbours0, Node, Neighbours),
 458        Tree = node(root, Neighbours)
 459    ;   path_up(node(Parent, [Node]), Tree)
 460    ).
 461path_up(Tree, Tree).
 462
 463
 464%!  man_child_of(?Child, ?Parent) is nondet.
 465%
 466%   Query the manual hierarchy.
 467
 468man_child_of(Child, Parent) :-
 469    term_hash(Child, ChildHash),
 470    term_hash(Parent, ParentHash),
 471    man_child_of(ChildHash, Child, ParentHash, Parent).
 472
 473:- dynamic
 474    man_child_of/4,
 475    man_tree_done/0.
 476
 477%!  ensure_man_tree
 478%
 479%   Materialize the manual tree as a binary relation.
 480
 481ensure_man_tree :-
 482    man_tree_done,
 483    !.
 484ensure_man_tree :-
 485    with_mutex(man_tree,
 486               make_man_tree).
 487
 488make_man_tree :-
 489    man_tree_done,
 490    !.
 491make_man_tree :-
 492    man_content_tree(swi('doc/Manual'), ManTree),
 493    man_packages_tree(PkgTree),
 494    assert_tree(node(root, [ManTree, PkgTree])),
 495    assertz(man_tree_done).
 496
 497assert_tree(node(Id, Children)) :-
 498    !,
 499    maplist(assert_parent(Id), Children),
 500    maplist(assert_tree, Children).
 501assert_tree(_).
 502
 503assert_parent(Id, Child) :-
 504    node_id(Child, ChildId),
 505    term_hash(Id, ParentHash),
 506    term_hash(ChildId, ChildHash),
 507    assertz(man_child_of(ChildHash, ChildId, ParentHash, Id)).
 508
 509node_id(node(Id, _), Id) :- !.
 510node_id(Id, Id).
 511
 512
 513%!  man_content_tree(+Dir, -Tree) is det.
 514%
 515%   Compute the content tree for a   multi-file HTML document. We do
 516%   this by processing =Contents.html= for  making the toplevel tree
 517%   that   links   to   the   individual    files.   Then   we   use
 518%   html_content_tree/2 to materialize the trees for the files.
 519
 520man_content_tree(Spec, node(manual, Chapters)) :-
 521    absolute_file_name(Spec, Dir,
 522                       [ file_type(directory),
 523                         access(read)
 524                       ]),
 525    directory_file_path(Dir, 'Contents.html', ContentsFile),
 526    load_html_file(ContentsFile, DOM),
 527    findall(Level-Path,
 528            ( xpath(DOM, //div(@class=Class), DIV),
 529              class_level(Class, Level),
 530              xpath(DIV, a(@class=sec,@href=File), _),
 531              \+ sub_atom(File, _, _, _, #),
 532              directory_file_path(Dir, File, Path)
 533            ),
 534            Pairs),
 535    index_chapters(Pairs, Chapters).
 536
 537class_level('toc-h1', 1).
 538class_level('toc-h2', 2).
 539class_level('toc-h3', 3).
 540class_level('toc-h4', 4).
 541
 542index_chapters([], []).
 543index_chapters([Level-File|T0], [node(Chapter, Children)|T]) :-
 544    html_content_tree(File, Node),
 545    Node = node(Chapter, Children0),
 546    append(Children0, Sections, Children),
 547    index_sections(T0, Level, Sections, T1),
 548    index_chapters(T1, T).
 549
 550index_sections([], _, [], []) :- !.
 551index_sections([SLevel-File|T0], Level, [Node|T], Rest) :-
 552    SLevel > Level,
 553    !,
 554    html_content_tree(File, Node),
 555    index_sections(T0, Level, T, Rest).
 556index_sections(Rest, _, [], Rest).
 557
 558
 559%!  man_packages_tree(-Tree) is det.
 560%
 561%   Tree is the content tree of all packages
 562
 563man_packages_tree(node(packages, Packages)) :-
 564    index_manual,
 565    Section = section(0, _, _, _),
 566    findall(File,
 567            man_index(Section, _Title, File, packages, _),
 568            Files),
 569    maplist(package_node, Files, Packages).
 570
 571package_node(File, Tree) :-
 572    html_content_tree(File, Tree).
 573
 574%!  html_content_tree(+ManualFile, -Tree) is det.
 575%
 576%   True when Tree represents the  hierarchical structure of objects
 577%   documented in the HTML file ManualFile. Tree  is a term where of
 578%   the form below. Object is a   documentation  object (typically a
 579%   section  or  predicate  indicator)  that    may   be  handed  to
 580%   object_link//1  and  similar  predicates  to  make  a  table  of
 581%   contents.
 582%
 583%       node(Object, ListOfTree).
 584
 585html_content_tree(File, Tree) :-
 586    index_manual,
 587    findall(Offset-Obj,
 588            man_index(Obj, _Summary, File, _Class, Offset),
 589            Pairs),
 590    keysort(Pairs, Sorted),
 591    pairs_values(Sorted, Objects),
 592    make_tree(Objects, Trees),
 593    assertion(Trees = [_]),
 594    Trees = [Tree].
 595
 596make_tree([], []).
 597make_tree([Obj|T0], [node(Obj, Children)|T]) :-
 598    children(T0, Obj, Children, T1),
 599    make_tree(T1, T).
 600
 601children([], _, [], []) :- !.
 602children([Obj|T0], Root, [Node|T], Rest) :-
 603    section_level(Obj, ObjLevel),
 604    section_level(Root, Level),
 605    ObjLevel > Level,
 606    !,
 607    Node = node(Obj, Children),
 608    children(T0, Obj, Children, T1),
 609    children(T1, Root, T, Rest).
 610children([Obj|T0], Root, [Obj|T], Rest) :-
 611    \+ section_level(Obj, _),
 612    !,
 613    children(T0, Root, T, Rest).
 614children(Rest, _, [], Rest).
 615
 616section_level(section(Level, _Nr, _Id, _File), Level).
 617
 618
 619                 /*******************************
 620                 *            RETRIEVE          *
 621                 *******************************/
 622
 623%!  load_man_object(+Obj, -Parent, -Path, -DOM) is nondet.
 624%
 625%   load the desription of the  object   matching  Obj from the HTML
 626%   sources and return the DT/DD pair in DOM.
 627%
 628%   @tbd    Nondet?
 629
 630load_man_object(Obj, ParentSection, Path, DOM) :-
 631    resolve_section(Obj, For),
 632    For = section(_,SN,_ID,Path),
 633    parent_section(For, ParentSection),
 634    findall(Nr-Pos, section_start(Path, Nr, Pos), Pairs),
 635    (   (   Pairs = [SN-_|_]
 636        ;   Pairs == []
 637        )
 638    ->  !,
 639        load_html_file(Path, DOM)           % Load whole file
 640    ;   append(_, [SN-Start|Rest], Pairs)
 641    ->  !,
 642        (   member(N-End, Rest),
 643            \+ sub_atom(N, 0, _, _, SN),
 644            Len is End - Start,
 645            Options = [content_length(Len)]
 646        ->  true
 647        ;   Options = []
 648        ),
 649        open(Path, read, In, [type(binary)]),
 650        seek(In, Start, bof, _),
 651        dtd(html, DTD),
 652        new_sgml_parser(Parser,
 653                        [ dtd(DTD)
 654                        ]),
 655        set_sgml_parser(Parser, file(Path)),
 656        set_sgml_parser(Parser, dialect(sgml)),
 657        set_sgml_parser(Parser, shorttag(false)),
 658        set_sgml_parser(Parser, defaults(false)),
 659        call_cleanup(sgml_parse(Parser,
 660                                [ document(DOM),
 661                                  source(In),
 662                                  syntax_errors(quiet)
 663                                | Options
 664                                ]),
 665                     ( free_sgml_parser(Parser),
 666                       close(In)
 667                     ))
 668    ).
 669load_man_object(For, Parent, Path, DOM) :-
 670    index_manual,
 671    object_spec(For, Obj),
 672    man_index(Obj, _, Path, _, Position),
 673    (   object_section(Path, Position, Parent)
 674    ->  true
 675    ;   Parent = Path
 676    ),
 677    open(Path, read, In, [type(binary)]),
 678    seek(In, Position, bof, _),
 679    dtd(html, DTD),
 680    new_sgml_parser(Parser,
 681                    [ dtd(DTD)
 682                    ]),
 683    set_sgml_parser(Parser, file(Path)),
 684    set_sgml_parser(Parser, dialect(sgml)),
 685    set_sgml_parser(Parser, shorttag(false)),
 686    set_sgml_parser(Parser, defaults(false)),
 687    call_cleanup(parse_dts_upto_dd(Parser, In, DOM),
 688                 ( free_sgml_parser(Parser),
 689                   close(In)
 690                 )).
 691
 692parse_dts_upto_dd(Parser, In, Description) :-
 693    sgml_parse(Parser,
 694               [ document(DOM0),
 695                 source(In),
 696                 parse(element),
 697                 syntax_errors(quiet)
 698               ]),
 699    (   DOM0 = [Element],
 700        Element = element(dt, _, _)
 701    ->  Description = [Element|More],
 702        parse_dts_upto_dd(Parser, In, More)
 703    ;   Description = DOM0
 704    ).
 705
 706section_start(Path, Nr, Pos) :-
 707    index_manual,
 708    man_index(section(_,Nr,_,_), _, Path, _, Pos).
 709
 710%!  resolve_section(+SecIn, -SecOut) is det.
 711%
 712%   Resolve symbolic path reference and fill   in  level and section
 713%   number if this information is missing.   The latter allows us to
 714%   refer to files of the manual.
 715
 716resolve_section(section(Level, No, Spec), Section) :-
 717    !,
 718    resolve_section(section(Level, No, _, Spec), Section).
 719resolve_section(section(Level, No, ID, Path),
 720                section(Level, No, ID, Path)) :-
 721    nonvar(ID),
 722    index_manual,
 723    man_index(section(Level,No,ID,Path), _, _, _, _),
 724    !.
 725resolve_section(section(Level, No, ID, Spec),
 726                section(Level, No, ID, Path)) :-
 727    ground(Spec),
 728    absolute_file_name(Spec, Path,
 729                       [ access(read)
 730                       ]),
 731    (   index_manual,
 732        man_index(section(Level, No, ID, Path), _, _, _, _)
 733    ->  true
 734    ;   path_allowed(Path)
 735    ->  true
 736    ;   permission_error(read, manual_file, Spec)
 737    ).
 738
 739
 740path_allowed(Path) :-                   % allow all files from swi/doc
 741    absolute_file_name(swi(doc), Parent,
 742                       [ access(read),
 743                         file_type(directory)
 744                       ]),
 745    sub_atom(Path, 0, _, _, Parent).
 746
 747
 748%!  parent_section(+Section, -Parent) is det.
 749%
 750%   Parent is the parent-section  of   Section.  First  computes the
 751%   section number and than finds the   required  number in the same
 752%   file or same directory. If this doesn't exist, get the file as a
 753%   whole.
 754
 755parent_section(section(Level, Nr, _ID, File), Parent) :-
 756    integer(Level),
 757    Parent = section(PL, PNr, _PID, _PFile),
 758    PL is Level - 1,
 759    findall(B, sub_atom(Nr, B, _, _, '.'), BL),
 760    last(BL, Before),
 761    sub_atom(Nr, 0, Before, _, PNr),
 762    (   man_index(Parent, _, File, _, _)
 763    ->  true
 764    ;   man_index(Parent, _, ParentFile, _, _),
 765        same_dir(File, ParentFile)
 766    ->  true
 767    ;   man_index(Parent, _, _, _, _)
 768    ),
 769    !.
 770parent_section(section(Level, _, _, File), Parent) :-
 771    Parent = section(ParentLevel, _, _, File),
 772    man_index(Parent, _, _, _, _),
 773    ParentLevel < Level,
 774    !.
 775parent_section(section(_, _, _, File), File).
 776
 777
 778%!  object_section(+Path, +Position, -Section) is semidet.
 779%
 780%   Section is the section in which object appears.  This is the
 781%   last section object before position.
 782
 783object_section(Path, Pos, Section) :-
 784    Section = section(_,_,_,_),
 785    findall(Section,
 786           (man_index(Section, _, Path, _, SecPos), SecPos =< Pos),
 787            List),
 788    last(List, Section).
 789
 790same_dir(File1, File2) :-
 791    file_directory_name(File1, Dir),
 792    file_directory_name(File2, Dir).
 793
 794%!  object_spec(+Atom, -SpecTerm)
 795%
 796%   Tranform the Name/Arity, etc strings as   received from the HTTP
 797%   into a term.  Must return unique results.
 798
 799object_spec(Spec, Spec).
 800object_spec(Atom, Spec) :-
 801    catch(atom_to_term(Atom, Spec, _), _, fail),
 802    !,
 803    Atom \== Spec.
 804object_spec(Atom, PI) :-
 805    name_to_object(Atom, PI).
 806
 807
 808                 /*******************************
 809                 *            EMIT              *
 810                 *******************************/
 811
 812%!  man_page(+Obj, +Options)// is semidet.
 813%
 814%   Produce a Prolog manual page for  Obj.   The  page consists of a
 815%   link to the section-file and  a   search  field, followed by the
 816%   predicate description.  Obj is one of:
 817%
 818%       * Name/Arity
 819%       Predicate indicator: display documentation of the predicate
 820%
 821%       * f(Name/Arity)
 822%       display documentation of an arithmetic function
 823%
 824%       * c(Function)
 825%       display documentation of a C API function
 826%
 827%       * section(Level, Number, Id, File)
 828%       Display a section of the manual
 829%
 830%       * sec(DocFile#Id)
 831%       Display a section of the manual (from short form)
 832%
 833%   Options:
 834%
 835%           * no_manual(Action)
 836%           If Action = =fail=, fail instead of displaying a
 837%           not-found message.
 838%
 839%           * links(Bool)
 840%           If =true= (default), include links to the parent object;
 841%           if =false=, just emit the manual material.
 842
 843man_page(Obj, Options) -->
 844    { ground(Obj),
 845      special_node(Obj)
 846    },
 847    !,
 848    html_requires(pldoc),
 849    man_links([], Options),
 850    man_matches([Obj], Obj, Options).
 851man_page(Obj0, Options) -->                     % Manual stuff
 852    { full_page(Obj0, Obj),
 853      findall((Parent+Path)-(Obj+DOM),
 854              load_man_object(Obj, Parent, Path, DOM),
 855              Matches),
 856      Matches = [_|_],
 857      !,
 858      pairs_keys(Matches, ParentPaths),
 859      Matches = [Parent+Path-_|_]
 860    },
 861    html_requires(pldoc),
 862    man_links(ParentPaths, Options),
 863    man_matches(Matches, Obj, Options).
 864man_page(Obj, Options) -->                      % PlDoc predicates, etc.
 865    { full_object(Obj, Full),
 866      findall(Full-File,
 867              ( doc_comment(Full, File:_, _, _),
 868                \+ private(Full, Options)
 869              ),
 870              Pairs),
 871      Pairs \== [],
 872      pairs_keys(Pairs, Objs)
 873    },
 874    !,
 875    html_requires(pldoc),
 876    (   { Pairs = [_-File] }
 877    ->  object_page_header(File, Options)
 878    ;   object_page_header(-, Options)
 879    ),
 880    objects(Objs, [ synopsis(true),
 881                    navtree(true)
 882                  | Options
 883                  ]).
 884man_page(Obj, Options) -->                      % failure
 885    { \+ option(no_manual(fail), Options)
 886    },
 887    html_requires(pldoc),
 888    man_links([], Options),
 889    html(p(class(noman),
 890           [ 'Sorry, No manual entry for ',
 891             b('~w'-[Obj])
 892           ])).
 893
 894%special_node(manual).          % redirected to the Introduction section
 895special_node(root).
 896special_node(packages).
 897
 898full_page(Obj, _) :-
 899    var(Obj), !, fail.
 900full_page(Obj, Obj) :-
 901    Obj = section(_,_,_,_),
 902    !.
 903full_page(section(ID), section(_,_,ID,_)) :- !.
 904full_page(manual, section(_,_,'sec:intro',_)) :- !.
 905full_page(Obj0, Obj) :-
 906    index_manual,
 907    ground(Obj0),
 908    alt_obj(Obj0, Obj),
 909    man_index(Obj, _, _, _, _),
 910    !.
 911full_page(Obj, Obj) :-
 912    ground(Obj).
 913
 914alt_obj(Obj, Obj).
 915alt_obj(Name/Arity, Name//DCGArity) :-
 916    integer(Arity),
 917    Arity >= 2,
 918    DCGArity is Arity - 2.
 919alt_obj(Name//DCGArity, Name/Arity) :-
 920    integer(DCGArity),
 921    Arity is DCGArity + 2.
 922
 923%!  full_object(+Object, -Full) is semidet.
 924%
 925%   Translate to canonical PlDoc object
 926
 927full_object(Object, M:Obj) :-
 928    qualify(Object, M:Obj0),
 929    alt_obj(Obj0, Obj),
 930    doc_comment(M:Obj, _, _, _),
 931    !.
 932
 933qualify(M:O, M:O).
 934qualify(O, _:O).
 935
 936%!  man_qualified_object(+Text, +Parent, -Object, -Section) is semidet.
 937%
 938%   Get a qualified predicate description from  Text that appears in
 939%   the section Parent.
 940%
 941%   The tricky part is that there   are cases where multiple modules
 942%   export the same predicate. We must find   from  the title of the
 943%   manual section which library is documented.
 944
 945
 946man_qualified_object(Text, Parent, Object, Section) :-
 947    atom(Text),
 948    atom_pi(Text, PI),
 949    ground(PI),
 950    !,
 951    man_qualified_object_2(PI, Parent, Object, Section).
 952man_qualified_object(Object0, Parent, Object, Section) :-
 953    man_qualified_object_2(Object0, Parent, Object, Section).
 954
 955man_qualified_object_2(Name/Arity, Parent, Module:Name/Arity, Section) :-
 956    object_module(Parent, Module, Section),
 957    !.
 958man_qualified_object_2(Object, Parent, Object, Parent).
 959
 960
 961%!  man_synopsis(+Object, +Section)//
 962%
 963%   Give synopsis details for a  fully specified predicate indicator
 964%   and link this to the section.
 965
 966:- public
 967    man_synopsis//2.                % called from man_match//2
 968
 969man_synopsis(PI, Section) -->
 970    { object_href(Section, HREF)
 971    },
 972    object_synopsis(PI, [href(HREF)]).
 973
 974%!  object_module(+Section0, -Module, -Section) is semidet.
 975%
 976%   Find the module documented by Section.
 977%
 978%   @tbd This requires that the documented file is loaded. If
 979%   not, should we use the title of the section?
 980
 981object_module(Section0, Module, Section) :-
 982    parent_section_ndet(Section0, Section),
 983    man_index(Section, Title, _File, _Class, _Offset),
 984    (   once(sub_atom(Title, B, _, _, :)),
 985        sub_atom(Title, 0, B, _, Atom),
 986        catch(term_to_atom(Term, Atom), _, fail),
 987        ground(Term),
 988        Term = library(_)
 989    ->  !,
 990        absolute_file_name(Term, PlFile,
 991                           [ file_type(prolog),
 992                             access(read),
 993                             file_errors(fail)
 994                           ]),
 995        module_property(Module, file(PlFile))
 996    ).
 997
 998parent_section_ndet(Section, Section).
 999parent_section_ndet(Section, Parent) :-
1000    parent_section(Section, Parent0),
1001    parent_section_ndet(Parent0, Parent).
1002
1003
1004man_matches(Matches, Object, Options) -->
1005    { option(navtree(false), Options) },
1006    !,
1007    man_matches_nt(Matches, Object, Options).
1008man_matches(Matches, Object, Options) -->
1009    html([ div(class(navtree),
1010               div(class(navwindow),
1011                   \man_nav_tree(Object, Options))),
1012           div(class(navcontent),
1013               \man_matches_nt(Matches, Object, Options))
1014         ]).
1015
1016
1017man_matches_nt([Match], Object, Options) -->
1018    { option(footer(true), Options, true) },
1019    !,
1020    man_match(Match, Object),
1021    object_page_footer(Object, []).
1022man_matches_nt(Matches, Object, _) -->
1023    man_matches_list(Matches, Object).
1024
1025man_matches_list([], _) --> [].
1026man_matches_list([H|T], Obj) --> man_match(H, Obj), man_matches_list(T, Obj).
1027
1028%!  man_match(+Term, +Object)//
1029%
1030%   If  possible,  insert  the  synopsis  into   the  title  of  the
1031%   description.
1032
1033man_match(packages, packages) -->
1034    !,
1035    html({|html||
1036              <p>
1037              Packages are relatively independent add-on libraries that
1038              may not be available in all installations.
1039             |}).
1040man_match(root, root) -->
1041    !,
1042    man_overview([]).
1043man_match((Parent+Path)-(Obj+[element(dt,A,C0)|DD]), Obj) -->
1044    { man_qualified_object(Obj, Parent, QObj, Section),
1045      !,
1046      C = [ span(style('float:right;margin-left:5px;'),
1047                 \object_source_button(QObj, [link_source(true)]))
1048          | C0
1049          ]
1050    },
1051    dom_list([ element(dt,[],[\man_synopsis(QObj, Section)]),
1052               element(dt,A,C)
1053             | DD
1054             ], Path).
1055man_match((_Parent+Path)-(Obj+DOM), Obj) -->
1056    dom_list(DOM, Path).
1057
1058
1059:- html_meta
1060    dom_list(html, +, ?, ?).
1061
1062dom_list(_:[], _) -->
1063    !,
1064    [].
1065dom_list(M:[H|T], Path) -->
1066    dom(H, Path),
1067    dom_list(M:T, Path).
1068
1069dom(element(E, Atts, Content), Path) -->
1070    !,
1071    dom_element(E, Atts, Content, Path).
1072dom(CDATA, _) -->
1073    html(CDATA).
1074
1075dom_element(a, _, [], _) -->                   % Useless back-references
1076    !,
1077    [].
1078dom_element(a, Att, Content, Path) -->
1079    { memberchk(href=HREF, Att),
1080      (   memberchk(class=Class, Att)
1081      ->  true
1082      ;   Class = unknown
1083      ),
1084      rewrite_ref(Class, HREF, Path, Myref)
1085    },
1086    !,
1087    html(a(href(Myref), \dom_list(Content, Path))).
1088dom_element(span, Att, [CDATA], _) -->
1089    { memberchk(class='pred-ext', Att),
1090      atom_pi(CDATA, PI),
1091      documented(PI),
1092      http_link_to_id(pldoc_man, [predicate=CDATA], HREF)
1093    },
1094    !,
1095    html(a(href(HREF), CDATA)).
1096dom_element(img, Att0, [], Path) -->
1097    { selectchk(src=Src, Att0, Att1),
1098      current_prolog_flag(home, SWI),
1099      sub_atom(Path, 0, Len, _, SWI),
1100      (   sub_atom(Path, Len, _, _, '/doc/Manual/')
1101      ->  Handler = manual_file
1102      ;   sub_atom(Path, Len, _, _, '/doc/packages/')
1103      ->  Handler = pldoc_package
1104      ),
1105      !,
1106      http_link_to_id(Handler, [], ManRef),
1107      directory_file_path(ManRef, Src, NewPath),
1108      Begin =.. [img, src(NewPath) | Att1]
1109    },
1110    !,
1111    html_begin(Begin),
1112    html_end(img).
1113dom_element(div, Att, _, _) -->
1114    { memberchk(class=navigate, Att) },
1115    !.
1116dom_element(html, _, Content, Path) -->        % do not emit a html for the second time
1117    !,
1118    dom_list(Content, Path).
1119dom_element(head, _, Content, Path) -->        % do not emit a head for the second time
1120    !,
1121    dom_list(Content, Path).
1122dom_element(title, _, _, _) --> !.
1123dom_element(link, _, _, _) --> !.
1124dom_element(body, _, Content, Path) -->        % do not emit a body for the second time
1125    !,
1126    dom_list(Content, Path).
1127dom_element(Name, Attrs, Content, Path) -->
1128    { Begin =.. [Name|Attrs] },
1129    html_begin(Begin),
1130    dom_list(Content, Path),
1131    html_end(Name).
1132
1133%!  documented(+PI) is semidet.
1134%
1135%   True if we have documentation about PI
1136
1137documented(PI) :-
1138    index_manual,
1139    man_index(PI, _, _, _, _),
1140    !.
1141documented(PI) :-
1142    full_object(PI, _Obj).
1143
1144%!  rewrite_ref(+Class, +Ref0, +Path, -ManRef) is semidet.
1145%
1146%   Rewrite Ref0 from the HTML reference manual format to the server
1147%   format. Reformatted:
1148%
1149%       $ File#Name/Arity :
1150%       Local reference using the manual presentation
1151%       =|/man?predicate=PI|=.
1152%
1153%       $ File#sec:NR :
1154%       Rewrite to =|section(Level, NT, ID, FilePath)|=
1155%
1156%       $ File#flag:Name :
1157%       Rewrite to =|section(Level, NT, ID, FilePath)#flag:Name|=
1158%
1159%       $ File#Name()
1160%       Rewrite to /man/CAPI=Name
1161%
1162%   @param Class    Class of the <A>.  Supported classes are
1163%
1164%           | sec  | Link to a section     |
1165%           | pred | Link to a predicate   |
1166%           | flag | link to a Prolog flag |
1167%
1168%   @param Ref0     Initial reference from the =a= element
1169%   @param Path     Currently loaded file
1170%   @param ManRef   PlDoc server reference
1171
1172rewrite_ref(pred, Ref0, _, Ref) :-              % Predicate/DCG reference
1173    sub_atom(Ref0, _, _, A, '#'),
1174    !,
1175    sub_atom(Ref0, _, A, 0, Fragment),
1176    name_to_object(Fragment, PI),
1177    man_index(PI, _, _, _, _),
1178    uri_encoded(query_value, Fragment, Enc),
1179    http_location_by_id(pldoc_man, ManHandler),
1180    format(string(Ref), '~w?predicate=~w', [ManHandler, Enc]).
1181rewrite_ref(function, Ref0, _, Ref) :-          % Arithmetic function reference
1182    sub_atom(Ref0, _, _, A, '#'),
1183    !,
1184    sub_atom(Ref0, _, A, 0, Fragment),
1185    name_to_object(Fragment, PI),
1186    man_index(PI, _, _, _, _),
1187    PI=f(Name/Arity),
1188    format(atom(PIName), '~w/~w', [Name,Arity]),
1189    uri_encoded(query_value, PIName, Enc),
1190    http_location_by_id(pldoc_man, ManHandler),
1191    format(string(Ref), '~w?function=~w', [ManHandler, Enc]).
1192rewrite_ref(func, Ref0, _, Ref) :-              % C-API reference
1193    sub_atom(Ref0, _, _, A, '#'),
1194    !,
1195    sub_atom(Ref0, _, A, 0, Fragment),
1196    name_to_object(Fragment, Obj),
1197    man_index(Obj, _, _, _, _),
1198    Obj = c(Function),
1199    uri_encoded(query_value, Function, Enc),
1200    http_location_by_id(pldoc_man, ManHandler),
1201    format(string(Ref), '~w?CAPI=~w', [ManHandler, Enc]).
1202rewrite_ref(sec, Ref0, Path, Ref) :-            % Section inside a file
1203    sub_atom(Ref0, B, _, A, '#'),
1204    !,
1205    sub_atom(Ref0, _, A, 0, Fragment),
1206    sub_atom(Ref0, 0, B, _, File),
1207    referenced_section(Fragment, File, Path, Section),
1208    object_href(Section, Ref).
1209rewrite_ref(sec, File, Path, Ref) :-            % Section is a file
1210    file_directory_name(Path, Dir),
1211    atomic_list_concat([Dir, /, File], SecPath),
1212    Obj = section(_, _, _, SecPath),
1213    man_index(Obj, _, _, _, _),
1214    !,
1215    object_href(Obj, Ref).
1216rewrite_ref(cite, Ref0, Path, Ref) :-           % Citation (bit hard-wired)
1217    debug(pldoc(cite), 'Cite ref ~q ~q', [Ref0, Path]),
1218    sub_atom(Ref0, _, _, A, '#'),
1219    !,
1220    sub_atom(Ref0, _, A, 0, Fragment),
1221    uri_encoded(query_value, Fragment, Enc),
1222    http_location_by_id(pldoc_man, ManHandler),
1223    format(string(Ref), '~w?section=bibliography#~w', [ManHandler, Enc]).
1224rewrite_ref(flag, Ref0, Path, Ref) :-
1225    sub_atom(Ref0, B, _, A, '#'),
1226    !,
1227    sub_atom(Ref0, 0, B, _, File),
1228    sub_atom(Ref0, _, A, 0, Fragment),
1229    file_directory_name(Path, Dir),
1230    atomic_list_concat([Dir, /, File], SecPath),
1231    Obj = section(_, _, _, SecPath),
1232    man_index(Obj, _, _, _, _),
1233    !,
1234    object_href(Obj, Ref1),
1235    format(string(Ref), '~w#~w', [Ref1, Fragment]).
1236
1237%!  name_to_object(+Atom, -PredicateIndicator) is semidet.
1238%
1239%   If Atom is `Name/Arity', decompose to Name and Arity. No errors.
1240
1241name_to_object(Atom, Object) :-
1242    atom(Atom),
1243    atom_pi(Atom, PI),
1244    ground(PI),
1245    (   PI = Name/Arity,
1246        integer(Arity),
1247        atom_concat('f-', FuncName, Name)
1248    ->  Object = f(FuncName/Arity)
1249    ;   Object = PI
1250    ).
1251name_to_object(Atom, c(Function)) :-
1252    atom(Atom),
1253    sub_atom(Atom, 0, _, _, 'PL_'),
1254    sub_atom(Atom, B, _, _, '('),
1255    !,
1256    sub_atom(Atom, 0, B, _, Function).
1257
1258
1259%!  referenced_section(+Fragment, +File, +Path, -Section)
1260
1261referenced_section(Fragment, File, Path, section(Level, Nr, ID, SecPath)) :-
1262    atom_concat('sec:', Nr, Fragment),
1263    (   File == ''
1264    ->  SecPath = Path
1265    ;   file_directory_name(Path, Dir),
1266        atomic_list_concat([Dir, /, File], SecPath)
1267    ),
1268    man_index(section(Level, Nr, ID, SecPath), _, _, _, _).
1269
1270
1271%!  man_links(+ParentPaths, +Options)// is det.
1272%
1273%   Create top link structure for manual pages.
1274
1275man_links(ParentPaths, Options) -->
1276    prolog:doc_page_header(parents(ParentPaths), Options),
1277    !.
1278man_links(ParentPaths, Options) -->
1279    { option(links(true), Options, true),
1280      option(header(true), Options, true)
1281    },
1282    !,
1283    html([ div(class(navhdr),
1284               [ div(class(jump), \man_parent(ParentPaths)),
1285                 div(class(search), \search_form(Options)),
1286                 br(clear(right))
1287               ]),
1288           p([])
1289         ]).
1290man_links(_, _) -->
1291    [].
1292
1293man_parent(ParentPaths) -->
1294    { maplist(parent_to_section, ParentPaths, [Section|MoreSections]),
1295      maplist(=(Section), MoreSections)
1296    },
1297    !,
1298    object_ref(Section, [secref_style(number_title)]).
1299man_parent(_) --> [].
1300
1301parent_to_section(X+_, X) :-
1302    X = section(_,_,_,_),
1303    !.
1304parent_to_section(File+_, Section) :-
1305    atom(File),
1306    man_index(Section, _Title, File, _Class, _Offset),
1307    !.
1308
1309%!  section_link(+Obj, +Options)// is det.
1310%
1311%   Create link to a section.  Options recognised:
1312%
1313%           * secref_style(+Style)
1314%           One of =number=, =title= or =number_title=.
1315
1316section_link(Section, Options) -->
1317    { option(secref_style(Style), Options, number)
1318    },
1319    section_link(Style, Section, Options).
1320
1321section_link(number, section(_, Number, _, _), _Options) -->
1322    !,
1323    (   {Number == '0'}             % Title.  Package?
1324    ->  []
1325    ;   html(['Sec. ', Number])
1326    ).
1327section_link(title, Obj, _Options) -->
1328    !,
1329    { man_index(Obj, Title, _File, _Class, _Offset)
1330    },
1331    html(Title).
1332section_link(_, Obj, _Options) -->
1333    !,
1334    { Obj = section(_, Number, _, _),
1335      man_index(Obj, Title, _File, _Class, _Offset)
1336    },
1337    (   { Number == '0' }
1338    ->  html(Title)
1339    ;   html([Number, ' ', Title])
1340    ).
1341
1342%!  function_link(+Function, +Options) is det.
1343%
1344%   Create a link to a C-function
1345
1346function_link(Function, _) -->
1347    html([Function, '()']).
1348
1349
1350                 /*******************************
1351                 *       INDICES & OVERVIEW     *
1352                 *******************************/
1353
1354%!  man_overview(+Options)// is det.
1355%
1356%   Provide a toplevel overview on the  manual: the reference manual
1357%   and the available packages.
1358
1359man_overview(Options) -->
1360    { http_absolute_location(pldoc_man(.), RefMan, [])
1361    },
1362    html([ h1('SWI-Prolog documentation'),
1363           blockquote(class(refman_link),
1364                      a(href(RefMan),
1365                        'SWI-Prolog reference manual')),
1366           \package_overview(Options),
1367           \paperback(Options)
1368         ]).
1369
1370package_overview(Options) -->
1371    html([ h2(class(package_doc_title),
1372              'SWI-Prolog package documentation'),
1373           blockquote(class(package_overview),
1374                      \packages(Options))
1375         ]).
1376
1377packages(Options) -->
1378    { findall(Pkg, current_package(Pkg), Pkgs)
1379    },
1380    packages(Pkgs, Options).
1381
1382packages([], _) -->
1383    [].
1384packages([Pkg|T], Options) -->
1385    package(Pkg, Options),
1386    packages(T, Options).
1387
1388package(pkg(Title, HREF, HavePackage), Options) -->
1389    { package_class(HavePackage, Class, Options)
1390    },
1391    html(div(class(Class),
1392             a([href(HREF)], Title))).
1393
1394package_class(true,  pkg_link, _).
1395package_class(false, no_pkg_link, _).
1396
1397current_package(pkg(Title, HREF, HavePackage)) :-
1398    man_index(section(0, _, _, _), Title, File, packages, _),
1399    file_base_name(File, FileNoDir),
1400    file_name_extension(Base, _, FileNoDir),
1401    (   exists_source(library(Base))
1402    ->  HavePackage = true
1403    ;   HavePackage = false
1404    ),
1405    http_absolute_location(pldoc_pkg(FileNoDir), HREF, []).
1406
1407
1408:- http_handler(pldoc(jpl),      pldoc_jpl,              [prefix]).
1409:- http_handler(pldoc_pkg(.),    pldoc_package,          [prefix]).
1410:- http_handler(pldoc_man(.),    pldoc_refman,           [prefix]).
1411:- http_handler(pldoc(packages), pldoc_package_overview, []).
1412
1413%!  pldoc_jpl(+Request)
1414%
1415%   Hack to include JPL documentation in server.
1416
1417pldoc_jpl(Request) :-
1418    memberchk(path_info(JPLFile), Request),
1419    atom_concat('doc/packages/jpl', JPLFile, Path),
1420    http_reply_file(swi(Path), [], Request).
1421
1422%!  pldoc_package(+Request)
1423%
1424%   HTTP  handler  for   PlDoc    package   documentation.   Accepts
1425%   /pldoc/package/<package>.{html,gif}.          The           path
1426%   =/pldoc/package/<package>= is redirected to the canonical object
1427%   version.
1428
1429pldoc_package(Request) :-
1430    (   \+ option(path_info(_), Request)
1431    ->  true
1432    ;   option(path_info(/), Request)
1433    ),
1434    http_link_to_id(pldoc_object, [object=packages], HREF),
1435    http_redirect(see_other, HREF, Request).
1436pldoc_package(Request) :-
1437    memberchk(path_info(Img), Request),
1438    file_mime_type(Img, image/_),
1439    !,
1440    atom_concat('doc/packages/', Img, Path),
1441    http_reply_file(swi(Path), [], Request).
1442pldoc_package(Request) :-
1443    memberchk(path_info('jpl'), Request),
1444    !,
1445    memberchk(path(Path0), Request),
1446    atom_concat(Path0, /, Path),
1447    http_redirect(moved, Path, Request).
1448pldoc_package(Request) :-
1449    memberchk(path_info(JPLFile), Request),
1450    (   JPLFile == 'jpl/'
1451    ->  Path = 'doc/packages/jpl/index.html'
1452    ;   sub_atom(JPLFile, 0, _, _, 'jpl/')
1453    ->  atom_concat('doc/packages/', JPLFile, Path)
1454    ),
1455    http_reply_file(swi(Path), [], Request).
1456pldoc_package(Request) :-
1457    memberchk(path_info(PkgDoc), Request),
1458    ensure_html_ext(PkgDoc, PkgHtml),
1459    atom_concat('packages/', PkgHtml, Path),
1460    term_to_atom(section(Path), Object),
1461    http_link_to_id(pldoc_object, [object=Object], HREF),
1462    http_redirect(see_other, HREF, Request).
1463
1464ensure_html_ext(Pkg, PkgHtml) :-
1465    file_name_extension(_, html, Pkg),
1466    !,
1467    PkgHtml = Pkg.
1468ensure_html_ext(Pkg, PkgHtml) :-
1469    file_name_extension(Pkg, html, PkgHtml).
1470
1471%!  pldoc_package_overview(+Request)
1472%
1473%   Provide an overview of the package documentation
1474
1475pldoc_package_overview(_Request) :-
1476    reply_html_page(
1477        pldoc(packages),
1478        title('SWI-Prolog package documentation'),
1479        \package_overview([])).
1480
1481%!  paperback(+Options)//
1482%
1483%   Link to the paperback version of the manual.
1484
1485paperback(_Options) -->
1486    { expand_url_path(swipl_book(.), HREF)
1487    },
1488    html([ h2('The manual as a book'),
1489           p([ 'A paperback version of the manual is ',
1490               a(href(HREF), 'available'), '.'
1491             ])
1492         ]).
1493
1494%!  pldoc_refman(+Request)
1495%
1496%   HTTP handler for PlDoc Reference Manual access.  Accepts
1497%   /refman/[<package>.html.]
1498
1499pldoc_refman(Request) :-
1500    memberchk(path_info(Section), Request),
1501    \+ sub_atom(Section, _, _, _, /),
1502    Obj = section(0,_,_,_),
1503    index_manual,
1504    man_index(Obj, Title, File, manual, _),
1505    file_base_name(File, Section),
1506    !,
1507    reply_html_page(pldoc(man),
1508                    title(Title),
1509                    \object_page(Obj, [])).
1510pldoc_refman(Request) :-                % server Contents.html
1511    \+ memberchk(path_info(_), Request),
1512    !,
1513    http_link_to_id(pldoc_object, [object(manual)], HREF),
1514    http_redirect(see_other, HREF, Request).
1515pldoc_refman(Request) :-
1516    memberchk(path(Path), Request),
1517    existence_error(http_location, Path).
1518
1519
1520                 /*******************************
1521                 *          HOOK SEARCH         *
1522                 *******************************/
1523
1524prolog:doc_object_summary(section(ID), Class, File, Summary) :-
1525    nonvar(ID),                     % when generating, only do full ones
1526    index_manual,
1527    man_index(section(_Level, _No, ID, _Path), Summary, File, Class, _Offset).
1528prolog:doc_object_summary(Obj, Class, File, Summary) :-
1529    index_manual,
1530    man_index(Obj, Summary, File, Class, _Offset).
1531
1532prolog:doc_object_page(Obj, Options) -->
1533    man_page(Obj, [no_manual(fail),footer(false)|Options]).
1534
1535%!  prolog:doc_object_link(+Obj, +Options)//
1536%
1537%   Provide the HTML to describe Obj for linking purposes.
1538
1539prolog:doc_object_link(Obj, Options) -->
1540    { Obj = section(_,_,_,_),
1541      index_manual
1542    },
1543    !,
1544    section_link(Obj, Options).
1545prolog:doc_object_link(Obj0, Options) -->
1546    { Obj0 = section(ID),
1547      Obj = section(_Level, _No, ID, _Path),
1548      index_manual,
1549      man_index(Obj, _, _, _, _)
1550    },
1551    !,
1552    section_link(Obj, Options).
1553prolog:doc_object_link(Obj, Options) -->
1554    { Obj = c(Function) },
1555    !,
1556    function_link(Function, Options).
1557prolog:doc_object_link(root, _) -->
1558    !,
1559    html('Documentation').
1560prolog:doc_object_link(manual, _Options) -->
1561    !,
1562    html('Reference manual').
1563prolog:doc_object_link(packages, _) -->
1564    html('Packages').
1565
1566prolog:doc_category(manual,   30, 'SWI-Prolog Reference Manual').
1567prolog:doc_category(packages, 40, 'Package documentation').
1568
1569prolog:doc_file_index_header(File, Options) -->
1570    { Section = section(_Level, _No, _ID, File),
1571      man_index(Section, _Summary, File, _Cat, _Offset)
1572    },
1573    !,
1574    html(tr(th([colspan(3), class(section)],
1575               [ \object_ref(Section,
1576                             [ secref_style(number_title)
1577                             | Options
1578                             ])
1579               ]))).
1580
1581prolog:doc_object_title(Obj, Title) :-
1582    Obj = section(_,_,_,_),
1583    man_index(Obj, Title, _, _, _),
1584    !.
1585
1586prolog:doc_canonical_object(section(_Level, _No, ID, _Path),
1587                            section(ID)).
1588
1589swi_local_path(Path, Local) :-
1590    atom(Path),
1591    is_absolute_file_name(Path),
1592    absolute_file_name(swi(doc), SWI,
1593                       [ file_type(directory),
1594                         solutions(all)
1595                       ]),
1596    directory_file_path(SWI, Local, Path),
1597    !.
1598
1599%!  prolog:doc_object_href(+Object, -HREF) is semidet.
1600%
1601%   Produce a HREF for section objects.
1602
1603prolog:doc_object_href(section(ID), HREF) :-
1604    nonvar(ID),
1605    atom_concat('sec:', Sec, ID),
1606    http_link_to_id(pldoc_man, [section(Sec)], HREF).
1607prolog:doc_object_href(section(_Level, _No, ID, _Path), HREF) :-
1608    nonvar(ID),
1609    atom_concat('sec:', Sec, ID),
1610    http_link_to_id(pldoc_man, [section(Sec)], HREF).
1611
1612
1613                 /*******************************
1614                 *           MESSAGES           *
1615                 *******************************/
1616
1617:- multifile prolog:message//1.
1618
1619prolog:message(pldoc(no_section_id(File, Title))) -->
1620    [ 'PlDoc: ~w: no id for section "~w"'-[File, Title] ].
1621prolog:message(pldoc(duplicate_ids(L))) -->
1622    [ 'PlDoc: duplicate manual section IDs:'-[], nl
1623    ],
1624    duplicate_ids(L).
1625
1626duplicate_ids([]) --> [].
1627duplicate_ids([H|T]) --> duplicate_id(H), duplicate_ids(T).
1628
1629duplicate_id(Id) -->
1630    { findall(File, man_index(section(_,_,Id,File),_,_,_,_), Files) },
1631    [ '    ~w: ~p'-[Id, Files], nl ].