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)  2007-2024, University of Amsterdam
    7                              VU University Amsterdam
    8                              SWI-Prolog Solutions b.v.
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(pldoc_latex,
   38          [ doc_latex/3,                % +Items, +OutFile, +Options
   39            latex_for_file/3,           % +FileSpec, +Out, +Options
   40            latex_for_wiki_file/3,      % +FileSpec, +Out, +Options
   41            latex_for_predicates/3      % +PI, +Out, +Options
   42          ]).   43:- use_module(library(pldoc)).   44:- use_module(library(readutil)).   45:- use_module(library(error)).   46:- use_module(library(apply)).   47:- use_module(library(option)).   48:- use_module(library(lists)).   49:- use_module(library(debug)).   50:- use_module(pldoc(doc_wiki)).   51:- use_module(pldoc(doc_process)).   52:- use_module(pldoc(doc_modes)).   53:- use_module(library(pairs), [pairs_values/2]).   54:- use_module(library(prolog_source), [file_name_on_path/2]).   55:- use_module(library(prolog_xref), [xref_hook/1]).   56:- use_module(pldoc(doc_html),          % we cannot import all as the
   57              [ doc_file_objects/5,     % \commands have the same name
   58                unquote_filespec/2,
   59                doc_tag_title/2,
   60                existing_linked_file/2,
   61                pred_anchor_name/3,
   62                private/2,
   63                (multifile)/2,
   64                is_pi/1,
   65                is_op_type/2
   66              ]).

PlDoc LaTeX backend

This module translates the Herbrand term from the documentation extracting module doc_wiki.pl into a LaTeX document for us with the pl.sty LaTeX style file. The function of this module is very similar to doc_html.pl, providing the HTML backend, and the implementation follows the same paradigm. The module can

author
- Jan Wielemaker */
To be done
- See TODO
   89:- predicate_options(doc_latex/3, 3,
   90                     [ stand_alone(boolean),
   91                       public_only(boolean),
   92                       section_level(oneof([section,subsection,subsubsection])),
   93                       summary(atom)
   94                     ]).   95:- predicate_options(latex_for_file/3, 3,
   96                     [ stand_alone(boolean),
   97                       public_only(boolean),
   98                       section_level(oneof([section,subsection,subsubsection]))
   99                     ]).  100:- predicate_options(latex_for_predicates/3, 3,
  101                     [                          % no options
  102                     ]).  103:- predicate_options(latex_for_wiki_file/3, 3,
  104                     [ stand_alone(boolean),
  105                       public_only(boolean),
  106                       section_level(oneof([section,subsection,subsubsection]))
  107                     ]).  108
  109
  110:- thread_local
  111    options/1,
  112    documented/1.  113
  114current_options(Options) :-
  115    options(Current),
  116    !,
  117    Options = Current.
  118current_options([]).
 doc_latex(+Spec, +OutFile, +Options) is det
Process one or more objects, writing the LaTeX output to OutFile. Spec is one of:
Name / Arity
Generate documentation for predicate
Name // Arity
Generate documentation for DCG rule
File
If File is a prolog file (as defined by prolog_file_type/2), process using latex_for_file/3, otherwise process using latex_for_wiki_file/3.

Typically Spec is either a list of filenames or a list of predicate indicators. Defined options are:

stand_alone(+Bool)
If true (default), create a document that can be run through LaTeX. If false, produce a document to be included in another LaTeX document.
public_only(+Bool)
If true (default), only emit documentation for exported predicates.
section_level(+Level)
Outermost section level produced. Level is the name of a LaTeX section command. Default is section.
summary(+File)
Write summary declarations to the named File.
modules(+List)
If [[Name/Arity]] needs to be resolved, search for the predicates in the given modules.
module(+Module)
Same as modules([Module]).
  156doc_latex(Spec, OutFile, Options) :-
  157    load_urldefs,
  158    merge_options(Options,
  159                  [ include_reexported(true)
  160                  ],
  161                  Options1),
  162    retractall(documented(_)),
  163    setup_call_cleanup(
  164        asserta(options(Options), Ref),
  165        phrase(process_items(Spec, [body], Options1), Tokens),
  166        erase(Ref)),
  167    setup_call_cleanup(
  168        open(OutFile, write, Out),
  169        print_latex(Out, Tokens, Options1),
  170        close(Out)),
  171    latex_summary(Options).
  172
  173process_items([], Mode, _) -->
  174    !,
  175    pop_mode(body, Mode, _).
  176process_items([H|T], Mode, Options) -->
  177    process_items(H, Mode, Mode1, Options),
  178    process_items(T, Mode1, Options).
  179process_items(Spec, Mode, Options) -->
  180    {Mode = [Mode0|_]},
  181    process_items(Spec, Mode, Mode1, Options),
  182    pop_mode(Mode0, Mode1, _).
  183
  184process_items(PI, Mode0, Mode, Options) -->
  185    { is_pi(PI) },
  186    !,
  187    need_mode(description, Mode0, Mode),
  188    latex_tokens_for_predicates(PI, Options).
  189process_items(FileSpec, Mode0, Mode, Options) -->
  190    {   (   absolute_file_name(FileSpec,
  191                               [ file_type(prolog),
  192                                 access(read),
  193                                 file_errors(fail)
  194                               ],
  195                               File)
  196        ->  true
  197        ;   absolute_file_name(FileSpec,
  198                               [ access(read)
  199                               ],
  200                               File)
  201        ),
  202        file_name_extension(_Base, Ext, File)
  203    },
  204    need_mode(body, Mode0, Mode),
  205    (   { user:prolog_file_type(Ext, prolog) }
  206    ->  latex_tokens_for_file(File, Options)
  207    ;   latex_tokens_for_wiki_file(File, Options)
  208    ).
 latex_for_file(+File, +Out, +Options) is det
Generate a LaTeX description of all commented predicates in File, writing the LaTeX text to the stream Out. Supports the options stand_alone, public_only and section_level. See doc_latex/3 for a description of the options.
  218latex_for_file(FileSpec, Out, Options) :-
  219    load_urldefs,
  220    phrase(latex_tokens_for_file(FileSpec, Options), Tokens),
  221    print_latex(Out, Tokens, Options).
 latex_tokens_for_file(+FileSpec, +Options)//
  226latex_tokens_for_file(FileSpec, Options, Tokens, Tail) :-
  227    absolute_file_name(FileSpec,
  228                       [ file_type(prolog),
  229                         access(read)
  230                       ],
  231                       File),
  232    doc_file_objects(FileSpec, File, Objects, FileOptions, Options),
  233    asserta(options(Options), Ref),
  234    call_cleanup(phrase(latex([ \file_header(File, FileOptions)
  235                              | \objects(Objects, FileOptions)
  236                              ]),
  237                        Tokens, Tail),
  238                 erase(Ref)).
 latex_for_wiki_file(+File, +Out, +Options) is det
Write a LaTeX translation of a Wiki file to the steam Out. Supports the options stand_alone, public_only and section_level. See doc_latex/3 for a description of the options.
  248latex_for_wiki_file(FileSpec, Out, Options) :-
  249    load_urldefs,
  250    phrase(latex_tokens_for_wiki_file(FileSpec, Options), Tokens),
  251    print_latex(Out, Tokens, Options).
  252
  253latex_tokens_for_wiki_file(FileSpec, Options, Tokens, Tail) :-
  254    absolute_file_name(FileSpec, File,
  255                       [ access(read)
  256                       ]),
  257    read_file_to_codes(File, String, []),
  258    b_setval(pldoc_file, File),
  259    asserta(options(Options), Ref),
  260    call_cleanup((wiki_codes_to_dom(String, [], DOM),
  261                  phrase(latex(DOM), Tokens, Tail)
  262                 ),
  263                 (nb_delete(pldoc_file),
  264                  erase(Ref))).
 latex_for_predicates(+PI:list, +Out, +Options) is det
Generate LaTeX for a list of predicate indicators. This does not produce the \begin{description}...\end{description} environment, just a plain list of \predicate, etc. statements. The current implementation ignores Options.
  274latex_for_predicates(Spec, Out, Options) :-
  275    load_urldefs,
  276    phrase(latex_tokens_for_predicates(Spec, Options), Tokens),
  277    print_latex(Out, [nl_exact(0)|Tokens], Options).
  278
  279latex_tokens_for_predicates([], _Options) --> !.
  280latex_tokens_for_predicates([H|T], Options) -->
  281    !,
  282    latex_tokens_for_predicates(H, Options),
  283    latex_tokens_for_predicates(T, Options).
  284latex_tokens_for_predicates(PI, Options) -->
  285    { generic_pi(PI),
  286      !,
  287      (   doc_comment(PI, Pos, _Summary, Comment)
  288      ->  true
  289      ;   Comment = ''
  290      )
  291    },
  292    object(PI, Pos, Comment, [description], _, Options).
  293latex_tokens_for_predicates(Spec, Options) -->
  294    { findall(PI, documented_pi(Spec, PI, Options), List),
  295      (   List == []
  296      ->  print_message(warning, pldoc(no_predicates_from(Spec)))
  297      ;   true
  298      )
  299    },
  300    latex_tokens_for_predicates(List, Options).
  301
  302documented_pi(Spec, PI, Options) :-
  303    option(modules(List), Options),
  304    member(M, List),
  305    generalise_spec(Spec, PI, M),
  306    doc_comment(PI, _Pos, _Summary, _Comment),
  307    !.
  308documented_pi(Spec, PI, Options) :-
  309    option(module(M), Options),
  310    generalise_spec(Spec, PI, M),
  311    doc_comment(PI, _Pos, _Summary, _Comment),
  312    !.
  313documented_pi(Spec, PI, _Options) :-
  314    generalise_spec(Spec, PI, _),
  315    doc_comment(PI, _Pos, _Summary, _Comment).
  316
  317generic_pi(Module:Name/Arity) :-
  318    atom(Module), atom(Name), integer(Arity),
  319    !.
  320generic_pi(Module:Name//Arity) :-
  321    atom(Module), atom(Name), integer(Arity).
  322
  323generalise_spec(Name/Arity, M:Name/Arity, M).
  324generalise_spec(Name//Arity, M:Name//Arity, M).
  325
  326
  327                 /*******************************
  328                 *       LATEX PRODUCTION       *
  329                 *******************************/
  330
  331:- thread_local
  332    fragile/0.                      % provided when in fragile mode
  333
  334latex([]) -->
  335    !,
  336    [].
  337latex(Atomic) -->
  338    { string(Atomic),
  339      atom_string(Atom, Atomic),
  340      sub_atom(Atom, 0, _, 0, 'LaTeX')
  341    },
  342    !,
  343    [ latex('\\LaTeX{}') ].
  344latex(Atomic) -->                       % can this actually happen?
  345    { atomic(Atomic),
  346      !,
  347      atom_string(Atom, Atomic),
  348      findall(x, sub_atom(Atom, _, _, _, '\n'), Xs),
  349      length(Xs, Lines)
  350    },
  351    (   {Lines == 0}
  352    ->  [ Atomic ]
  353    ;   [ nl(Lines) ]
  354    ).
  355latex(List) -->
  356    latex_special(List, Rest),
  357    !,
  358    latex(Rest).
  359latex(w(Word)) -->
  360    [ Word ].
  361latex([H|T]) -->
  362    !,
  363    (   latex(H)
  364    ->  latex(T)
  365    ;   { print_message(error, latex(failed(H))) },
  366        latex(T)
  367    ).
  368
  369% high level commands
  370latex(h1(Attrs, Content)) -->
  371    latex_section(0, Attrs, Content).
  372latex(h2(Attrs, Content)) -->
  373    latex_section(1, Attrs, Content).
  374latex(h3(Attrs, Content)) -->
  375    latex_section(2, Attrs, Content).
  376latex(h4(Attrs, Content)) -->
  377    latex_section(3, Attrs, Content).
  378latex(p(Content)) -->
  379    [ nl_exact(2) ],
  380    latex(Content).
  381latex(blockquote(Content)) -->
  382    latex(cmd(begin(quote))),
  383    latex(Content),
  384    latex(cmd(end(quote))).
  385latex(center(Content)) -->
  386    latex(cmd(begin(center))),
  387    latex(Content),
  388    latex(cmd(end(center))).
  389latex(a(Attrs, Content)) -->
  390    { attribute(href(HREF), Attrs) },
  391    (   {HREF == Content}
  392    ->  latex(cmd(url(url_escape(HREF))))
  393    ;   { atom_concat(#,Sec,HREF) }
  394    ->  latex([Content, ' (', cmd(secref(Sec)), ')'])
  395    ;   latex(cmd(href(url_escape(HREF), Content)))
  396    ).
  397latex(br(_)) -->
  398    latex(latex(\\)).
  399latex(hr(_)) -->
  400    latex(cmd(hrule)).
  401latex(code(CodeList)) -->
  402    { is_list(CodeList),
  403      !,
  404      atomic_list_concat(CodeList, Atom)
  405    },
  406    (   {fragile}
  407    ->  latex(cmd(const(Atom)))
  408    ;   [ verb(Atom) ]
  409    ).
  410latex(code(Code)) -->
  411    { identifier(Code) },
  412    !,
  413    latex(cmd(const(Code))).
  414latex(code(Code)) -->
  415    (   {fragile}
  416    ->  latex(cmd(const(Code)))
  417    ;   [ verb(Code) ]
  418    ).
  419latex(b(Code)) -->
  420    latex(cmd(textbf(Code))).
  421latex(strong(Code)) -->
  422    latex(cmd(textbf(Code))).
  423latex(i(Code)) -->
  424    latex(cmd(textit(Code))).
  425latex(var(Var)) -->
  426    latex(cmd(arg(Var))).
  427latex(pre(_Class, Code)) -->
  428    [ nl_exact(2), code(Code), nl_exact(2) ].
  429latex(ul(Content)) -->
  430    { if_short_list(Content, shortlist, itemize, Env) },
  431    latex(cmd(begin(Env))),
  432    latex(Content),
  433    latex(cmd(end(Env))).
  434latex(ol(Content)) -->
  435    latex(cmd(begin(enumerate))),
  436    latex(Content),
  437    latex(cmd(end(enumerate))).
  438latex(li(Content)) -->
  439    latex(cmd(item)),
  440    latex(Content).
  441latex(dl(_, Content)) -->
  442    latex(cmd(begin(description))),
  443    latex(Content),
  444    latex(cmd(end(description))).
  445latex(dd(_, Content)) -->
  446    latex(Content).
  447latex(dd(Content)) -->
  448    latex(Content).
  449latex(dt(class=term, \term(Text, Term, Bindings))) -->
  450    termitem(Text, Term, Bindings).
  451latex(dt(Content)) -->
  452    latex(cmd(item(opt(Content)))).
  453latex(table(Attrs, Content)) -->
  454    latex_table(Attrs, Content).
  455latex(\Cmd, List, Tail) :-
  456    call(Cmd, List, Tail).
  457
  458% low level commands
  459latex(latex(Text)) -->
  460    [ latex(Text) ].
  461latex(cmd(Term)) -->
  462    { Term =.. [Cmd|Args] },
  463    indent(Cmd),
  464    [ cmd(Cmd) ],
  465    latex_arguments(Args),
  466    outdent(Cmd).
  467
  468indent(begin) --> !,           [ nl(2) ].
  469indent(end) --> !,             [ nl_exact(1) ].
  470indent(section) --> !,         [ nl(2) ].
  471indent(subsection) --> !,      [ nl(2) ].
  472indent(subsubsection) --> !,   [ nl(2) ].
  473indent(item) --> !,            [ nl(1), indent(4) ].
  474indent(definition) --> !,      [ nl(1), indent(4) ].
  475indent(tag) --> !,             [ nl(1), indent(4) ].
  476indent(termitem) --> !,        [ nl(1), indent(4) ].
  477indent(prefixtermitem) --> !,  [ nl(1), indent(4) ].
  478indent(infixtermitem) --> !,   [ nl(1), indent(4) ].
  479indent(postfixtermitem) --> !, [ nl(1), indent(4) ].
  480indent(predicate) --> !,       [ nl(1), indent(4) ].
  481indent(dcg) --> !,             [ nl(1), indent(4) ].
  482indent(infixop) --> !,         [ nl(1), indent(4) ].
  483indent(prefixop) --> !,        [ nl(1), indent(4) ].
  484indent(postfixop) --> !,       [ nl(1), indent(4) ].
  485indent(predicatesummary) --> !,[ nl(1) ].
  486indent(dcgsummary) --> !,      [ nl(1) ].
  487indent(oppredsummary) --> !,   [ nl(1) ].
  488indent(hline) --> !,           [ nl(1) ].
  489indent(_) -->                  [].
  490
  491outdent(begin) --> !,           [ nl_exact(1) ].
  492outdent(end) --> !,             [ nl(2) ].
  493outdent(item) --> !,            [ ' ' ].
  494outdent(tag) --> !,             [ nl(1) ].
  495outdent(termitem) --> !,        [ nl(1) ].
  496outdent(prefixtermitem) --> !,  [ nl(1) ].
  497outdent(infixtermitem) --> !,   [ nl(1) ].
  498outdent(postfixtermitem) --> !, [ nl(1) ].
  499outdent(definition) --> !,      [ nl(1) ].
  500outdent(section) --> !,         [ nl(2) ].
  501outdent(subsection) --> !,      [ nl(2) ].
  502outdent(subsubsection) --> !,   [ nl(2) ].
  503outdent(predicate) --> !,       [ nl(1) ].
  504outdent(dcg) --> !,             [ nl(1) ].
  505outdent(infixop) --> !,         [ nl(1) ].
  506outdent(prefixop) --> !,        [ nl(1) ].
  507outdent(postfixop) --> !,       [ nl(1) ].
  508outdent(predicatesummary) --> !,[ nl(1) ].
  509outdent(dcgsummary) --> !,      [ nl(1) ].
  510outdent(oppredsummary) --> !,   [ nl(1) ].
  511outdent(hline) --> !,           [ nl(1) ].
  512outdent(_) -->                  [].
 latex_special(String, Rest)// is semidet
Deals with special sequences of symbols.
  518latex_special(In, Rest) -->
  519    { url_chars(In, Chars, Rest),
  520      special(Chars),
  521      atom_chars(Atom, Chars),
  522      urldef_name(Atom, Name)
  523    },
  524    !,
  525    latex([cmd(Name), latex('{}')]).
  526
  527special(Chars) :-
  528    memberchk(\, Chars),
  529    !.
  530special(Chars) :-
  531    length(Chars, Len),
  532    Len > 1.
  533
  534url_chars([H|T0], [H|T], Rest) :-
  535    urlchar(H),
  536    !,
  537    url_chars(T0, T, Rest).
  538url_chars(L, [], L).
 latex_arguments(+Args:list)// is det
Write LaTeX command arguments. If an argument is of the form opt(Arg) it is written as [Arg], Otherwise it is written as {Arg}. Note that opt([]) is omitted. I think no LaTeX command is designed to handle an empty optional argument special.

During processing the arguments it asserts fragile/0 to allow is taking care of LaTeX fragile constructs (i.e. constructs that are not allows inside {...}).

  552latex_arguments(List, Out, Tail) :-
  553    asserta(fragile, Ref),
  554    call_cleanup(fragile_list(List, Out, Tail),
  555                 erase(Ref)).
  556
  557fragile_list([]) --> [].
  558fragile_list([opt([])|T]) -->
  559    !,
  560    fragile_list(T).
  561fragile_list([opt(H)|T]) -->
  562    !,
  563    [ '[' ],
  564    latex_arg(H),
  565    [ ']' ],
  566    fragile_list(T).
  567fragile_list([H|T]) -->
  568    [ curl(open) ],
  569    latex_arg(H),
  570    [ curl(close) ],
  571    fragile_list(T).
 latex_arg(+In)//
Write a LaTeX argument. If we can, we will use a defined urldef_name/2.
  578latex_arg(H) -->
  579    { atomic(H),
  580      atom_string(Atom, H),
  581      urldef_name(Atom, Name)
  582    },
  583    !,
  584    latex(cmd(Name)).
  585latex_arg(H) -->
  586    { maplist(atom, H),
  587      atomic_list_concat(H, Atom),
  588      urldef_name(Atom, Name)
  589    },
  590    !,
  591    latex(cmd(Name)).
  592latex_arg(no_escape(Text)) -->
  593    !,
  594    [no_escape(Text)].
  595latex_arg(url_escape(Text)) -->
  596    !,
  597    [url_escape(Text)].
  598latex_arg(H) -->
  599    latex(H).
  600
  601attribute(Att, Attrs) :-
  602    is_list(Attrs),
  603    !,
  604    option(Att, Attrs).
  605attribute(Att, One) :-
  606    option(Att, [One]).
  607
  608if_short_list(Content, If, Else, Env) :-
  609    (   short_list(Content)
  610    ->  Env = If
  611    ;   Env = Else
  612    ).
 short_list(+Content) is semidet
True if Content describes the content of a dl or ul/ol list where each elemenent has short content.
  619short_list([]).
  620short_list([_,dd(Content)|T]) :-
  621    !,
  622    short_content(Content),
  623    short_list(T).
  624short_list([_,dd(_, Content)|T]) :-
  625    !,
  626    short_content(Content),
  627    short_list(T).
  628short_list([li(Content)|T]) :-
  629    short_content(Content),
  630    short_list(T).
  631
  632short_content(Content) :-
  633    phrase(latex(Content), Tokens),
  634    summed_string_len(Tokens, 0, Len),
  635    Len < 50.
  636
  637summed_string_len([], Len, Len).
  638summed_string_len([H|T], L0, L) :-
  639    atomic(H),
  640    !,
  641    atom_length(H, AL),
  642    L1 is L0 + AL,
  643    summed_string_len(T, L1, L).
  644summed_string_len([_|T], L0, L) :-
  645    summed_string_len(T, L0, L).
 latex_section(+Level, +Attributes, +Content)// is det
Emit a LaTeX section, keeping track of the desired highest section level.
Arguments:
Level- Desired level, relative to the base-level. Must be a non-negative integer.
  656latex_section(Level, Attrs, Content) -->
  657    { current_options(Options),
  658      option(section_level(LaTexSection), Options, section),
  659      latex_section_level(LaTexSection, BaseLevel),
  660      FinalLevel is BaseLevel+Level,
  661      (   latex_section_level(SectionCommand, FinalLevel)
  662      ->  Term =.. [SectionCommand, Content]
  663      ;   domain_error(latex_section_level, FinalLevel)
  664      )
  665    },
  666    latex(cmd(Term)),
  667    section_label(Attrs).
  668
  669section_label(Attrs) -->
  670    { is_list(Attrs),
  671      memberchk(id(Name), Attrs),
  672      !,
  673      delete_unsafe_label_chars(Name, SafeName),
  674      atom_concat('sec:', SafeName, Label)
  675    },
  676    latex(cmd(label(Label))).
  677section_label(_) -->
  678    [].
  679
  680latex_section_level(chapter,       0).
  681latex_section_level(section,       1).
  682latex_section_level(subsection,    2).
  683latex_section_level(subsubsection, 3).
  684latex_section_level(paragraph,     4).
  685
  686deepen_section_level(Level0, Level1) :-
  687    latex_section_level(Level0, N),
  688    N1 is N + 1,
  689    latex_section_level(Level1, N1).
 delete_unsafe_label_chars(+LabelIn, -LabelOut)
delete unsafe characters from LabelIn. Currently only deletes _, as this appears commonly through filenames, but cannot be handled through the LaTeX processing chain.
  697delete_unsafe_label_chars(LabelIn, LabelOut) :-
  698    atom_chars(LabelIn, Chars),
  699    delete(Chars, '_', CharsOut),
  700    atom_chars(LabelOut, CharsOut).
  701
  702
  703                 /*******************************
  704                 *         \ COMMANDS           *
  705                 *******************************/
 include(+File, +Type, +Options)// is det
Called from [[File]].
  711include(PI, predicate, _) -->
  712    !,
  713    (   {   options(Options)
  714        ->  true
  715        ;   Options = []
  716        },
  717        latex_tokens_for_predicates(PI, Options)
  718    ->  []
  719    ;   latex(cmd(item(['[[', \predref(PI), ']]'])))
  720    ).
  721include(File, Type, Options) -->
  722    { existing_linked_file(File, Path) },
  723    !,
  724    include_file(Path, Type, Options).
  725include(File, _, _) -->
  726    latex(code(['[[', File, ']]'])).
  727
  728include_file(Path, image, Options) -->
  729    { option(caption(Caption), Options) },
  730    !,
  731    latex(cmd(begin(figure, [no_escape(htbp)]))),
  732    latex(cmd(begin(center))),
  733    latex(cmd(includegraphics(Path))),
  734    latex(cmd(end(center))),
  735    latex(cmd(caption(Caption))),
  736    latex(cmd(end(figure))).
  737include_file(Path, image, _) -->
  738    !,
  739    latex(cmd(includegraphics(Path))).
  740include_file(Path, Type, _) -->
  741    { assertion(memberchk(Type, [prolog,wiki])),
  742      current_options(Options0),
  743      select_option(stand_alone(_), Options0, Options1, _),
  744      select_option(section_level(Level0), Options1, Options2, section),
  745      deepen_section_level(Level0, Level),
  746      Options = [stand_alone(false), section_level(Level)|Options2]
  747    },
  748    (   {Type == prolog}
  749    ->  latex_tokens_for_file(Path, Options)
  750    ;   latex_tokens_for_wiki_file(Path, Options)
  751    ).
 file(+File, +Options)// is det
Called from implicitely linked files. The HTML version creates a hyperlink. We just name the file.
  758file(File, _Options) -->
  759    { fragile },
  760    !,
  761    latex(cmd(texttt(File))).
  762file(File, _Options) -->
  763    latex(cmd(file(File))).
 predref(+PI)// is det
Called from name/arity or name//arity patterns in the documentation.
  770predref(Module:Name/Arity) -->
  771    !,
  772    latex(cmd(qpredref(Module, Name, Arity))).
  773predref(Module:Name//Arity) -->
  774    latex(cmd(qdcgref(Module, Name, Arity))).
  775predref(Name/Arity) -->
  776    latex(cmd(predref(Name, Arity))).
  777predref(Name//Arity) -->
  778    latex(cmd(dcgref(Name, Arity))).
 nopredref(+PI)//
Called from name/arity.
  784nopredref(Name/Arity) -->
  785    latex(cmd(nopredref(Name, Arity))).
 flagref(+Flag)//
Reference to a Prolog flag
  791flagref(Flag) -->
  792    latex(cmd(prologflag(Flag))).
 cite(+Citations) is det
Emit a \cite{Citations} command
  798cite(Citations) -->
  799    { atomic_list_concat(Citations, ',', Atom) },
  800    latex(cmd(cite(Atom))).
 tags(+Tags:list(Tag)) is det
Emit tag list produced by the Wiki processor from the @keyword commands.
  807tags([\args(Params)|Rest]) -->
  808    !,
  809    args(Params),
  810    tags_list(Rest).
  811tags(List) -->
  812    tags_list(List).
  813
  814tags_list([]) -->
  815    [].
  816tags_list(List) -->
  817    [ nl(2) ],
  818    latex(cmd(begin(tags))),
  819    latex(List),
  820    latex(cmd(end(tags))),
  821    [ nl(2) ].
 tag(+Tag, +Values:list)// is det
Called from \tag(Name, Values) terms produced by doc_wiki.pl.
  827tag(Tag, [One]) -->
  828    !,
  829    { doc_tag_title(Tag, Title) },
  830    latex([ cmd(tag(Title))
  831          | One
  832          ]).
  833tag(Tag, More) -->
  834    { doc_tag_title(Tag, Title) },
  835    latex([ cmd(mtag(Title)),
  836            \tag_value_list(More)
  837          ]).
  838
  839tag_value_list([H|T]) -->
  840    latex(['- '|H]),
  841    (   { T \== [] }
  842    ->  [latex(' \\\\')],
  843        tag_value_list(T)
  844    ;   []
  845    ).
 args(+Params:list) is det
Called from \args(List) created by doc_wiki.pl. Params is a list of arg(Name, Descr).
  852args(Params) -->
  853    latex([ cmd(begin(arguments)),
  854            \arg_list(Params),
  855            cmd(end(arguments))
  856          ]).
  857
  858arg_list([]) -->
  859    [].
  860arg_list([H|T]) -->
  861    argument(H),
  862    arg_list(T).
  863
  864argument(arg(Name,Descr)) -->
  865    [ nl(1) ],
  866    latex(cmd(arg(Name))), [ latex(' & ') ],
  867    latex(Descr), [latex(' \\\\')].
 file_header(+File, +Options)// is det
Create the file header.
  873file_header(File, Options) -->
  874    { memberchk(file(Title, Comment), Options),
  875      !,
  876      file_synopsis(File, Synopsis)
  877    },
  878    file_title([Synopsis, ': ', Title], File, Options),
  879    { is_structured_comment(Comment, Prefixes),
  880      string_codes(Comment, Codes),
  881      indented_lines(Codes, Prefixes, Lines),
  882      section_comment_header(Lines, _Header, Lines1),
  883      wiki_lines_to_dom(Lines1, [], DOM0),
  884      tags_to_front(DOM0, DOM)
  885    },
  886    latex(DOM),
  887    latex(cmd(vspace('0.7cm'))).
  888file_header(File, Options) -->
  889    { file_synopsis(File, Synopsis)
  890    },
  891    file_title([Synopsis], File, Options).
  892
  893tags_to_front(DOM0, DOM) :-
  894    append(Content, [\tags(Tags)], DOM0),
  895    !,
  896    DOM = [\tags(Tags)|Content].
  897tags_to_front(DOM, DOM).
  898
  899file_synopsis(File, Synopsis) :-
  900    file_name_on_path(File, Term),
  901    unquote_filespec(Term, Unquoted),
  902    format(atom(Synopsis), '~w', [Unquoted]).
 file_title(+Title:list, +File, +Options)// is det
Emit the file-header and manipulation buttons.
  909file_title(Title, File, Options) -->
  910    { option(section_level(Level), Options, section),
  911      Section =.. [Level,Title],
  912      file_base_name(File, BaseExt),
  913      file_name_extension(Base, _, BaseExt),
  914      delete_unsafe_label_chars(Base, SafeBase),
  915      atom_concat('sec:', SafeBase, Label)
  916    },
  917    latex(cmd(Section)),
  918    latex(cmd(label(Label))).
 objects(+Objects:list, +Options)// is det
Emit the documentation body.
  925objects(Objects, Options) -->
  926    objects(Objects, [body], Options).
  927
  928objects([], Mode, _) -->
  929    pop_mode(body, Mode, _).
  930objects([Obj|T], Mode, Options) -->
  931    object(Obj, Mode, Mode1, Options),
  932    objects(T, Mode1, Options).
  933
  934object(doc(Obj,Pos,Comment), Mode0, Mode, Options) -->
  935    !,
  936    object(Obj, Pos, Comment, Mode0, Mode, Options).
  937object(Obj, Mode0, Mode, Options) -->
  938    { doc_comment(Obj, Pos, _Summary, Comment)
  939    },
  940    !,
  941    object(Obj, Pos, Comment, Mode0, Mode, Options).
  942
  943object(Obj, Pos, Comment, Mode0, Mode, Options) -->
  944    { is_pi(Obj),
  945      !,
  946      is_structured_comment(Comment, Prefixes),
  947      string_codes(Comment, Codes),
  948      indented_lines(Codes, Prefixes, Lines),
  949      strip_module(user:Obj, Module, _),
  950      process_modes(Lines, Module, Pos, Modes, Args, Lines1),
  951      (   private(Obj, Options)
  952      ->  Class = privdef           % private definition
  953      ;   multifile(Obj, Options)
  954      ->  Class = multidef
  955      ;   Class = pubdef            % public definition
  956      ),
  957      (   Obj = Module:_
  958      ->  POptions = [module(Module)|Options]
  959      ;   POptions = Options
  960      ),
  961      DOM = [\pred_dt(Modes, Class, POptions), dd(class=defbody, DOM1)],
  962      wiki_lines_to_dom(Lines1, Args, DOM0),
  963      strip_leading_par(DOM0, DOM1),
  964      assert_documented(Obj)
  965    },
  966    need_mode(description, Mode0, Mode),
  967    latex(DOM).
  968object([Obj|Same], Pos, Comment, Mode0, Mode, Options) -->
  969    !,
  970    object(Obj, Pos, Comment, Mode0, Mode, Options),
  971    { maplist(assert_documented, Same) }.
  972object(Obj, _Pos, _Comment, Mode, Mode, _Options) -->
  973    { debug(pldoc, 'Skipped ~p', [Obj]) },
  974    [].
  975
  976assert_documented(Obj) :-
  977    assert(documented(Obj)).
 need_mode(+Mode:atom, +Stack:list, -NewStack:list)// is det
While predicates are part of a description list, sections are not and we therefore need to insert <dl>...</dl> into the output. We do so by demanding an outer environment and push/pop the required elements.
  987need_mode(Mode, Stack, Stack) -->
  988    { Stack = [Mode|_] },
  989    !,
  990    [].
  991need_mode(Mode, Stack, Rest) -->
  992    { memberchk(Mode, Stack)
  993    },
  994    !,
  995    pop_mode(Mode, Stack, Rest).
  996need_mode(Mode, Stack, [Mode|Stack]) -->
  997    !,
  998    latex(cmd(begin(Mode))).
  999
 1000pop_mode(Mode, Stack, Stack) -->
 1001    { Stack = [Mode|_] },
 1002    !,
 1003    [].
 1004pop_mode(Mode, [H|Rest0], Rest) -->
 1005    latex(cmd(end(H))),
 1006    pop_mode(Mode, Rest0, Rest).
 pred_dt(+Modes, +Class, Options)// is det
Emit the \predicate{}{}{} header.
Arguments:
Modes- List as returned by process_modes/5.
Class- One of privdef or pubdef.
To be done
- Determinism
 1018pred_dt(Modes, Class, Options) -->
 1019    [nl(2)],
 1020    pred_dt(Modes, [], _Done, [class(Class)|Options]).
 1021
 1022pred_dt([], Done, Done, _) -->
 1023    [].
 1024pred_dt([H|T], Done0, Done, Options) -->
 1025    pred_mode(H, Done0, Done1, Options),
 1026    (   {T == []}
 1027    ->  []
 1028    ;   latex(cmd(nodescription)),
 1029        pred_dt(T, Done1, Done, Options)
 1030    ).
 1031
 1032pred_mode(mode(Head,Vars), Done0, Done, Options) -->
 1033    !,
 1034    { bind_vars(Head, Vars) },
 1035    pred_mode(Head, Done0, Done, Options).
 1036pred_mode(Head is Det, Done0, Done, Options) -->
 1037    !,
 1038    anchored_pred_head(Head, Done0, Done, [det(Det)|Options]).
 1039pred_mode(Head, Done0, Done, Options) -->
 1040    anchored_pred_head(Head, Done0, Done, Options).
 1041
 1042bind_vars(Term, Bindings) :-
 1043    bind_vars(Bindings),
 1044    anon_vars(Term).
 1045
 1046bind_vars([]).
 1047bind_vars([Name=Var|T]) :-
 1048    Var = '$VAR'(Name),
 1049    bind_vars(T).
 anon_vars(+Term) is det
Bind remaining variables in Term to '$VAR'('_'), so they are printed as '_'.
 1056anon_vars(Var) :-
 1057    var(Var),
 1058    !,
 1059    Var = '$VAR'('_').
 1060anon_vars(Term) :-
 1061    compound(Term),
 1062    !,
 1063    Term =.. [_|Args],
 1064    maplist(anon_vars, Args).
 1065anon_vars(_).
 1066
 1067
 1068anchored_pred_head(Head, Done0, Done, Options) -->
 1069    { pred_anchor_name(Head, PI, _Name) },
 1070    (   { memberchk(PI, Done0) }
 1071    ->  { Done = Done0 }
 1072    ;   { Done = [PI|Done0] }
 1073    ),
 1074    pred_head(Head, Options).
 pred_head(+Term, Options) is det
Emit a predicate head. The functor is typeset as a span using class pred and the arguments and var using class arglist.
To be done
- Support determinism in operators
 1084pred_head(//(Head), Options) -->
 1085    !,
 1086    { pred_attributes(Options, Atts),
 1087      Head =.. [Functor|Args],
 1088      length(Args, Arity)
 1089    },
 1090    latex(cmd(dcg(opt(Atts), Functor, Arity, \pred_args(Args, 1)))).
 1091pred_head(Head, _Options) -->                   % Infix operators
 1092    { Head =.. [Functor,Left,Right],
 1093      Functor \== (:),
 1094      is_op_type(Functor, infix), !
 1095    },
 1096    latex(cmd(infixop(Functor, \pred_arg(Left, 1), \pred_arg(Right, 2)))).
 1097pred_head(Head, _Options) -->                   % Prefix operators
 1098    { Head =.. [Functor,Arg],
 1099      is_op_type(Functor, prefix), !
 1100    },
 1101    latex(cmd(prefixop(Functor, \pred_arg(Arg, 1)))).
 1102pred_head(Head, _Options) -->                   % Postfix operators
 1103    { Head =.. [Functor,Arg],
 1104      is_op_type(Functor, postfix), !
 1105    },
 1106    latex(cmd(postfixop(Functor, \pred_arg(Arg, 1)))).
 1107pred_head(M:Head, Options) -->                 % Qualified predicates
 1108    !,
 1109    { pred_attributes(Options, Atts),
 1110      Head =.. [Functor|Args],
 1111      length(Args, Arity)
 1112    },
 1113    latex(cmd(qpredicate(opt(Atts),
 1114                         M,
 1115                         Functor, Arity, \pred_args(Args, 1)))).
 1116pred_head(Head, Options) -->                    % Plain terms
 1117    { pred_attributes(Options, Atts),
 1118      Head =.. [Functor|Args],
 1119      length(Args, Arity)
 1120    },
 1121    latex(cmd(predicate(opt(Atts),
 1122                        Functor, Arity, \pred_args(Args, 1)))).
 pred_attributes(+Options, -Attributes) is det
Create a comma-separated list of predicate attributes, such as determinism, etc.
 1129pred_attributes(Options, Attrs) :-
 1130    findall(A, pred_att(Options, A), As),
 1131    insert_comma(As, Attrs).
 1132
 1133pred_att(Options, Det) :-
 1134    option(det(Det), Options).
 1135pred_att(Options, private) :-
 1136    option(class(privdef), Options).
 1137pred_att(Options, multifile) :-
 1138    option(class(multidef), Options).
 1139
 1140insert_comma([H1,H2|T0], [H1, ','|T]) :-
 1141    !,
 1142    insert_comma([H2|T0], T).
 1143insert_comma(L, L).
 1144
 1145
 1146:- if(current_predicate(is_dict/1)). 1147dict_kv_pairs([]) --> [].
 1148dict_kv_pairs([H|T]) -->
 1149    dict_kv(H),
 1150    (   { T == [] }
 1151    ->  []
 1152    ;   latex(', '),
 1153        dict_kv_pairs(T)
 1154    ).
 1155
 1156dict_kv(Key-Value) -->
 1157    latex(cmd(key(Key))),
 1158    latex(':'),
 1159    term(Value).
 1160:- endif. 1161
 1162pred_args([], _) -->
 1163    [].
 1164pred_args([H|T], I) -->
 1165    pred_arg(H, I),
 1166    (   {T==[]}
 1167    ->  []
 1168    ;   latex(', '),
 1169        { I2 is I + 1 },
 1170        pred_args(T, I2)
 1171    ).
 1172
 1173pred_arg(Var, I) -->
 1174    { var(Var) },
 1175    !,
 1176    latex(['Arg', I]).
 1177pred_arg(...(Term), I) -->
 1178    !,
 1179    pred_arg(Term, I),
 1180    latex(cmd(ldots)).
 1181pred_arg(Term, I) -->
 1182    { Term =.. [Ind,Arg],
 1183      mode_indicator(Ind)
 1184    },
 1185    !,
 1186    latex([Ind, \pred_arg(Arg, I)]).
 1187pred_arg(Arg:Type, _) -->
 1188    !,
 1189    latex([\argname(Arg), :, \argtype(Type)]).
 1190pred_arg(Arg, _) -->
 1191    { atom(Arg) },
 1192    !,
 1193    argname(Arg).
 1194pred_arg(Arg, _) -->
 1195    argtype(Arg).                   % arbitrary term
 1196
 1197argname('$VAR'(Name)) -->
 1198    !,
 1199    latex(Name).
 1200argname(Name) -->
 1201    !,
 1202    latex(Name).
 1203
 1204argtype(Term) -->
 1205    { format(string(S), '~W',
 1206             [ Term,
 1207               [ quoted(true),
 1208                 numbervars(true)
 1209               ]
 1210             ]) },
 1211    latex(S).
 term(+Text, +Term, +Bindings)// is det
Process the \term element as produced by doc_wiki.pl.
To be done
- Properly merge with pred_head//1
 1219term(_, Term, Bindings) -->
 1220    { bind_vars(Bindings) },
 1221    term(Term).
 1222
 1223term('$VAR'(Name)) -->
 1224    !,
 1225    latex(cmd(arg(Name))).
 1226term(Compound) -->
 1227    { callable(Compound),
 1228      !,
 1229      Compound =.. [Functor|Args]
 1230    },
 1231    !,
 1232    term_with_args(Functor, Args).
 1233term(Rest) -->
 1234    latex(Rest).
 1235
 1236term_with_args(Functor, [Left, Right]) -->
 1237    { is_op_type(Functor, infix) },
 1238    !,
 1239    latex(cmd(infixterm(Functor, \term(Left), \term(Right)))).
 1240term_with_args(Functor, [Arg]) -->
 1241    { is_op_type(Functor, prefix) },
 1242    !,
 1243    latex(cmd(prefixterm(Functor, \term(Arg)))).
 1244term_with_args(Functor, [Arg]) -->
 1245    { is_op_type(Functor, postfix) },
 1246    !,
 1247    latex(cmd(postfixterm(Functor, \term(Arg)))).
 1248term_with_args(Functor, Args) -->
 1249    latex(cmd(term(Functor, \pred_args(Args, 1)))).
 termitem(+Text, +Term, +Bindings)// is det
Create a termitem or one of its variations.
 1256termitem(_Text, Term, Bindings) -->
 1257    { bind_vars(Bindings) },
 1258    termitem(Term).
 1259
 1260termitem('$VAR'(Name)) -->
 1261    !,
 1262    latex(cmd(termitem(var(Name), ''))).
 1263:- if(current_predicate(is_dict/1)). 1264termitem(Dict) -->
 1265    { is_dict(Dict),
 1266      !,
 1267      dict_pairs(Dict, Tag, Pairs)
 1268    },
 1269    latex(cmd(dictitem(Tag, \dict_kv_pairs(Pairs)))).
 1270:- endif. 1271termitem(Compound) -->
 1272    { callable(Compound),
 1273      !,
 1274      Compound =.. [Functor|Args]
 1275    },
 1276    !,
 1277    termitem_with_args(Functor, Args).
 1278termitem(Rest) -->
 1279    latex(cmd(termitem(Rest, ''))).
 1280
 1281termitem_with_args(Functor, [Left, Right]) -->
 1282    { is_op_type(Functor, infix) },
 1283    !,
 1284    latex(cmd(infixtermitem(Functor, \term(Left), \term(Right)))).
 1285termitem_with_args(Functor, [Arg]) -->
 1286    { is_op_type(Functor, prefix) },
 1287    !,
 1288    latex(cmd(prefixtermitem(Functor, \term(Arg)))).
 1289termitem_with_args(Functor, [Arg]) -->
 1290    { is_op_type(Functor, postfix) },
 1291    !,
 1292    latex(cmd(postfixtermitem(Functor, \term(Arg)))).
 1293termitem_with_args({}, [Arg]) -->
 1294    !,
 1295    latex(cmd(curltermitem(\argtype(Arg)))).
 1296termitem_with_args(Functor, Args) -->
 1297    latex(cmd(termitem(Functor, \pred_args(Args, 1)))).
 latex_table(+Attrs, +Content)// is det
Emit a table in LaTeX.
 1304latex_table(_Attrs, Content) -->
 1305    { max_columns(Content, 0, _, -, Wittness),
 1306      col_align(Wittness, 1, Content, Align),
 1307      atomics_to_string(Align, '|', S0),
 1308      atomic_list_concat(['|',S0,'|'], Format)
 1309    },
 1310%       latex(cmd(begin(table, opt(h)))),
 1311    latex(cmd(begin(quote))),
 1312    latex(cmd(begin(tabulary,
 1313                    no_escape('0.9\\textwidth'),
 1314                    no_escape(Format)))),
 1315    latex(cmd(hline)),
 1316    rows(Content),
 1317    latex(cmd(hline)),
 1318    latex(cmd(end(tabulary))),
 1319    latex(cmd(end(quote))).
 1320%       latex(cmd(end(table))).
 1321
 1322max_columns([], C, C, W, W).
 1323max_columns([tr(List)|T], C0, C, _, W) :-
 1324    length(List, C1),
 1325    C1 >= C0,		% take last as wittness to avoid getting the header
 1326    !,
 1327    max_columns(T, C1, C, List, W).
 1328max_columns([_|T], C0, C, W0, W) :-
 1329    max_columns(T, C0, C, W0, W).
 1330
 1331col_align([], _, _, []).
 1332col_align([CH|CT], Col, Rows, [AH|AT]) :-
 1333    (   member(tr(Cells), Rows),
 1334        nth1(Col, Cells, Cell),
 1335        auto_par(Cell)
 1336    ->  Wrap = auto
 1337    ;   Wrap = false
 1338    ),
 1339    col_align(CH, Wrap, AH),
 1340    Col1 is Col+1,
 1341    col_align(CT, Col1, Rows, AT).
 1342
 1343col_align(td(class=Class,_), Wrap, Align) :-
 1344    align_class(Class, Wrap, Align),
 1345    !.
 1346col_align(_, auto, 'L') :- !.
 1347col_align(_, false, 'l').
 1348
 1349align_class(left,   auto, 'L').
 1350align_class(center, auto, 'C').
 1351align_class(right,  auto, 'R').
 1352align_class(left,   false, 'l').
 1353align_class(center, false, 'c').
 1354align_class(right,  false, 'r').
 1355
 1356rows([]) -->
 1357    [].
 1358rows([tr(Content)|T]) -->
 1359    row(Content),
 1360    rows(T).
 1361
 1362row([]) -->
 1363    [ latex(' \\\\'), nl(1) ].
 1364row([td(_Attrs, Content)|T]) -->
 1365    !,
 1366    row([td(Content)|T]).
 1367row([td(Content)|T]) -->
 1368    latex(Content),
 1369    (   {T == []}
 1370    ->  []
 1371    ;   [ latex(' & ') ]
 1372    ),
 1373    row(T).
 1374row([th(Content)|T]) -->
 1375    latex(cmd(textbf(Content))),
 1376    (   {T == []}
 1377    ->  []
 1378    ;   [ latex(' & ') ]
 1379    ),
 1380    row(T).
 auto_par(+Content) is semidet
True when cell Content is a good candidate for auto-wrapping.
 1386auto_par(Content) :-
 1387    phrase(html_text(Content), Words),
 1388    length(Words, WC),
 1389    WC > 1,
 1390    atomics_to_string(Words, Text),
 1391    string_length(Text, Width),
 1392    Width > 15.
 1393
 1394html_text([]) -->
 1395    !.
 1396html_text([H|T]) -->
 1397    !,
 1398    html_text(H),
 1399    html_text(T).
 1400html_text(\predref(Name/Arity)) -->
 1401    !,
 1402    { format(string(S), '~q/~q', [Name, Arity]) },
 1403    [S].
 1404html_text(Compound) -->
 1405    { compound(Compound),
 1406      !,
 1407      functor(Compound, _Name, Arity),
 1408      arg(Arity, Compound, Content)
 1409    },
 1410    html_text(Content).
 1411html_text(Word) -->
 1412    [Word].
 1413
 1414
 1415
 1416
 1417                 /*******************************
 1418                 *      SUMMARY PROCESSING      *
 1419                 *******************************/
 latex_summary(+Options)
If Options contains summary(+File), write a summary of all documented predicates to File.
 1426latex_summary(Options) :-
 1427    option(summary(File), Options),
 1428    !,
 1429    findall(Obj, summary_obj(Obj), Objs),
 1430    maplist(pi_sort_key, Objs, Keyed),
 1431    keysort(Keyed, KSorted),
 1432    pairs_values(KSorted, SortedObj),
 1433    phrase(summarylist(SortedObj, Options), Tokens),
 1434    open(File, write, Out),
 1435    call_cleanup(print_latex(Out, Tokens, Options),
 1436                 close(Out)).
 1437latex_summary(_) :-
 1438    retractall(documented(_)).
 1439
 1440summary_obj(Obj) :-
 1441    documented(Obj),
 1442    pi_head(Obj, Head),
 1443    \+ xref_hook(Head).
 1444
 1445pi_head(M:PI, M:Head) :-
 1446    !,
 1447    pi_head(PI, Head).
 1448pi_head(Name/Arity, Head) :-
 1449    functor(Head, Name, Arity).
 1450pi_head(Name//DCGArity, Head) :-
 1451    Arity is DCGArity+2,
 1452    functor(Head, Name, Arity).
 1453
 1454
 1455pi_sort_key(M:PI, PI-(M:PI)) :- !.
 1456pi_sort_key(PI, PI-PI).
 1457
 1458object_name_arity(_:Term, Type, Name, Arity) :-
 1459    nonvar(Term),
 1460    !,
 1461    object_name_arity(Term, Type, Name, Arity).
 1462object_name_arity(Name/Arity, pred, Name, Arity).
 1463object_name_arity(Name//Arity, dcg, Name, Arity).
 1464
 1465summarylist(Objs, Options) -->
 1466    latex(cmd(begin(summarylist, ll))),
 1467    summary(Objs, Options),
 1468    latex(cmd(end(summarylist))).
 1469
 1470summary([], _) -->
 1471    [].
 1472summary([H|T], Options) -->
 1473    summary_line(H, Options),
 1474    summary(T, Options).
 1475
 1476summary_line(Obj, _Options) -->
 1477    { doc_comment(Obj, _Pos, Summary, _Comment),
 1478      !,
 1479      atom_codes(Summary, Codes),
 1480      phrase(pldoc_wiki:line_tokens(Tokens), Codes), % TBD: proper export
 1481      object_name_arity(Obj, Type, Name, Arity)
 1482    },
 1483    (   {Type == dcg}
 1484    ->  latex(cmd(dcgsummary(Name, Arity, Tokens)))
 1485    ;   { strip_module(Obj, M, _),
 1486          current_op(Pri, Ass, M:Name)
 1487        }
 1488    ->  latex(cmd(oppredsummary(Name, Arity, Ass, Pri, Tokens)))
 1489    ;   latex(cmd(predicatesummary(Name, Arity, Tokens)))
 1490    ).
 1491summary_line(Obj, _Options) -->
 1492    { print_message(warning, pldoc(no_summary_for(Obj)))
 1493    }.
 1494
 1495                 /*******************************
 1496                 *          PRINT TOKENS        *
 1497                 *******************************/
 1498
 1499print_latex(Out, Tokens, Options) :-
 1500    latex_header(Out, Options),
 1501    print_latex_tokens(Tokens, Out),
 1502    latex_footer(Out, Options).
 print_latex_tokens(+Tokens, +Out)
Print primitive LaTeX tokens to Output
 1509print_latex_tokens([], _).
 1510print_latex_tokens([nl(N)|T0], Out) :-
 1511    !,
 1512    max_nl(T0, T, N, NL),
 1513    nl(Out, NL),
 1514    print_latex_tokens(T, Out).
 1515print_latex_tokens([nl_exact(N)|T0], Out) :-
 1516    !,
 1517    nl_exact(T0, T,N, NL),
 1518    nl(Out, NL),
 1519    print_latex_tokens(T, Out).
 1520print_latex_tokens([H|T], Out) :-
 1521    print_latex_token(H, Out),
 1522    print_latex_tokens(T, Out).
 1523
 1524print_latex_token(cmd(Cmd), Out) :-
 1525    !,
 1526    format(Out, '\\~w', [Cmd]).
 1527print_latex_token(curl(open), Out) :-
 1528    !,
 1529    format(Out, '{', []).
 1530print_latex_token(curl(close), Out) :-
 1531    !,
 1532    format(Out, '}', []).
 1533print_latex_token(indent(N), Out) :-
 1534    !,
 1535    format(Out, '~t~*|', [N]).
 1536print_latex_token(nl(N), Out) :-
 1537    !,
 1538    format(Out, '~N', []),
 1539    forall(between(2,N,_), nl(Out)).
 1540print_latex_token(verb(Verb), Out) :-
 1541    is_list(Verb), Verb \== [],
 1542    !,
 1543    atomic_list_concat(Verb, Atom),
 1544    print_latex_token(verb(Atom), Out).
 1545print_latex_token(verb(Verb), Out) :-
 1546    !,
 1547    (   member(C, [$,'|',@,=,'"',^,!]),
 1548        \+ sub_atom(Verb, _, _, _, C)
 1549    ->  atom_replace_char(Verb, '\n', ' ', Verb2),
 1550        format(Out, '\\verb~w~w~w', [C,Verb2,C])
 1551    ;   assertion(fail)
 1552    ).
 1553print_latex_token(code(Code), Out) :-
 1554    !,
 1555    format(Out, '~N\\begin{code}~n', []),
 1556    format(Out, '~w', [Code]),
 1557    format(Out, '~N\\end{code}', []).
 1558print_latex_token(latex(Code), Out) :-
 1559    !,
 1560    write(Out, Code).
 1561print_latex_token(w(Word), Out) :-
 1562    !,
 1563    print_latex(Out, Word).
 1564print_latex_token(no_escape(Text), Out) :-
 1565    !,
 1566    write(Out, Text).
 1567print_latex_token(url_escape(Text), Out) :-
 1568    !,
 1569    print_url(Out, Text).
 1570print_latex_token(Rest, Out) :-
 1571    (   atomic(Rest)
 1572    ->  print_latex(Out, Rest)
 1573    ;   %type_error(latex_token, Rest)
 1574        write(Out, Rest)
 1575    ).
 1576
 1577atom_replace_char(In, From, To, Out) :-
 1578    sub_atom(In, _, _, _, From),
 1579    !,
 1580    atom_chars(In, CharsIn),
 1581    replace(CharsIn, From, To, CharsOut),
 1582    atom_chars(Out, CharsOut).
 1583atom_replace_char(In, _, _, In).
 1584
 1585replace([], _, _, []).
 1586replace([H|T0], H, N, [N|T]) :-
 1587    !,
 1588    replace(T0, H, N, T).
 1589replace([H|T0], F, N, [H|T]) :-
 1590    replace(T0, F, N, T).
 print_latex(+Out, +Text:atomic) is det
Print Text, such that it comes out as normal LaTeX text.
 1597print_latex(Out, String) :-
 1598    atom_string(Atom, String),
 1599    atom_chars(Atom, Chars),
 1600    print_chars(Chars, Out).
 1601
 1602print_chars([], _).
 1603print_chars([H|T], Out) :-
 1604    print_char(H, Out),
 1605    print_chars(T, Out).
 1606
 1607
 1608print_url(Out, String) :-
 1609    string_chars(String, Chars),
 1610    print_url_chars(Chars, Out).
 1611
 1612print_url_chars([], _).
 1613print_url_chars([H|T], Out) :-
 1614    print_url_char(H, Out),
 1615    print_url_chars(T, Out).
 1616
 1617print_url_char('#', Out) :- !, write(Out, '\\#').
 1618print_url_char(C,   Out) :- put_char(Out, C).
 max_nl(T0, T, M0, M)
Remove leading sequence of nl(N) and return the maximum of it.
 1625max_nl([nl(M1)|T0], T, M0, M) :-
 1626    !,
 1627    M2 is max(M1, M0),
 1628    max_nl(T0, T, M2, M).
 1629max_nl([nl_exact(M1)|T0], T, _, M) :-
 1630    !,
 1631    nl_exact(T0, T, M1, M).
 1632max_nl(T, T, M, M).
 1633
 1634nl_exact([nl(_)|T0], T, M0, M) :-
 1635    !,
 1636    max_nl(T0, T, M0, M).
 1637nl_exact([nl_exact(M1)|T0], T, M0, M) :-
 1638    !,
 1639    M2 is max(M1, M0),
 1640    max_nl(T0, T, M2, M).
 1641nl_exact(T, T, M, M).
 1642
 1643
 1644nl(Out, N) :-
 1645    forall(between(1, N, _), nl(Out)).
 1646
 1647
 1648print_char('<', Out) :- !, write(Out, '$<$').
 1649print_char('>', Out) :- !, write(Out, '$>$').
 1650print_char('{', Out) :- !, write(Out, '\\{').
 1651print_char('}', Out) :- !, write(Out, '\\}').
 1652print_char('$', Out) :- !, write(Out, '\\$').
 1653print_char('&', Out) :- !, write(Out, '\\&').
 1654print_char('#', Out) :- !, write(Out, '\\#').
 1655print_char('%', Out) :- !, write(Out, '\\%').
 1656print_char('~', Out) :- !, write(Out, '\\Stilde{}').
 1657print_char('\\',Out) :- !, write(Out, '\\bsl{}').
 1658print_char('^', Out) :- !, write(Out, '\\Shat{}').
 1659print_char('|', Out) :- !, write(Out, '\\Sbar{}').
 1660print_char('รถ', Out) :- !, write(Out, '\\"o').
 1661print_char(C,   Out) :- put_char(Out, C).
 identifier(+Atom) is semidet
True if Atom is (lower, alnum*).
 1668identifier(Atom) :-
 1669    atom_chars(Atom, [C0|Chars]),
 1670    char_type(C0, lower),
 1671    all_chartype(Chars, alnum).
 1672
 1673all_chartype([], _).
 1674all_chartype([H|T], Type) :-
 1675    char_type(H, Type),
 1676    all_chartype(T, Type).
 1677
 1678
 1679                 /*******************************
 1680                 *    LATEX SPECIAL SEQUENCES   *
 1681                 *******************************/
 urldef_name(?String, ?DefName)
True if \DefName is a urldef for String. UrlDefs are LaTeX sequences that can be used to represent strings with symbols in fragile environments. Whenever a word can be expressed with a urldef, we will do this to enhance the robustness of the generated LaTeX code.
 1691:- dynamic
 1692    urldef_name/2,
 1693    urlchar/1,                      % true if C appears in ine of them
 1694    urldefs_loaded/1.
 load_urldefs
 load_urldefs(+File)
Load \urldef definitions from File and populate urldef_name/2. See pldoc.sty for details.
 1702load_urldefs :-
 1703    urldefs_loaded(_),
 1704    !.
 1705load_urldefs :-
 1706    absolute_file_name(library('pldoc/pldoc.sty'), File,
 1707                       [ access(read) ]),
 1708    load_urldefs(File).
 1709
 1710load_urldefs(File) :-
 1711    urldefs_loaded(File),
 1712    !.
 1713load_urldefs(File) :-
 1714    open(File, read, In),
 1715    call_cleanup((   read_line_to_codes(In, L0),
 1716                     process_urldefs(L0, In)),
 1717                 close(In)),
 1718    assert(urldefs_loaded(File)).
 1719
 1720process_urldefs(end_of_file, _) :- !.
 1721process_urldefs(Line, In) :-
 1722    (   phrase(urldef(Name, String), Line)
 1723    ->  assert(urldef_name(String, Name)),
 1724        assert_chars(String)
 1725    ;   true
 1726    ),
 1727    read_line_to_codes(In, L2),
 1728    process_urldefs(L2, In).
 1729
 1730assert_chars(String) :-
 1731    atom_chars(String, Chars),
 1732    (   member(C, Chars),
 1733        \+ urlchar(C),
 1734        assert(urlchar(C)),
 1735        fail
 1736    ;   true
 1737    ).
 1738
 1739urldef(Name, String) -->
 1740    "\\urldef{\\", string(NameS), "}\\satom{", string(StringS), "}",
 1741    ws,
 1742    (   "%"
 1743    ->  string(_)
 1744    ;   []
 1745    ),
 1746    eol,
 1747    !,
 1748    { atom_codes(Name, NameS),
 1749      atom_codes(String, StringS)
 1750    }.
 1751
 1752ws --> [C], { C =< 32 }, !, ws.
 1753ws --> [].
 1754
 1755string([]) --> [].
 1756string([H|T]) --> [H], string(T).
 1757
 1758eol([],[]).
 1759
 1760
 1761                 /*******************************
 1762                 *         HEADER/FOOTER        *
 1763                 *******************************/
 1764
 1765latex_header(Out, Options) :-
 1766    (   option(stand_alone(true), Options, true)
 1767    ->  forall(header(Line), format(Out, '~w~n', [Line]))
 1768    ;   true
 1769    ),
 1770    forall(generated(Line), format(Out, '~w~n', [Line])).
 1771
 1772latex_footer(Out, Options) :-
 1773    (   option(stand_alone(true), Options, true)
 1774    ->  forall(footer(Line), format(Out, '~w~n', [Line]))
 1775    ;   true
 1776    ).
 1777
 1778header('\\documentclass[11pt]{article}').
 1779header('\\usepackage{times}').
 1780header('\\usepackage{pldoc}').
 1781header('\\sloppy').
 1782header('\\makeindex').
 1783header('').
 1784header('\\begin{document}').
 1785
 1786footer('').
 1787footer('\\printindex').
 1788footer('\\end{document}').
 1789
 1790generated('% This LaTeX document was generated using the LaTeX backend of PlDoc,').
 1791generated('% The SWI-Prolog documentation system').
 1792generated('').
 1793
 1794
 1795		 /*******************************
 1796		 *            MESSAGES		*
 1797		 *******************************/
 1798
 1799:- multifile
 1800    prolog:message//1. 1801
 1802prolog:message(pldoc(no_summary_for(Obj))) -->
 1803    [ 'No summary documentation for ~p'-[Obj] ]