1:- module(doc_latex, [latex_for_pack/3]).    2
    3:- ensure_loaded(library(pldoc)).    4
    5:- use_module(pldoc(doc_html)).    6
    7:- use_module(library(canny/files)).    8
    9%   There appears to be a problem with doc_latex/3. It back-tracks then
   10%   tries to load the list of input files. Work around the issue by
   11%   soft-cutting the redundant choice-point.
   12
   13%   Filter   out   undocumented   Prolog   source     files.   Use   the
   14%   doc_file_objects/5 predicate. The Objects argument (third) should be
   15%   a non-empty list of objects, also  the FileOptions (fourth argument)
   16%   can contain file-level documentation represented   by a file/2 term.
   17%   Document   either   way:   documented     predicates   exist,   file
   18%   documentation, or both.
 latex_for_pack(+Spec, +OutFile, +Options) is det
   22latex_for_pack(Spec, OutFile, Options) :-
   23    once(pack_file(Spec, PackFile)),
   24    file_directory_name(PackFile, Pack),
   25    bagof(File, latex_for_pack_(Pack, File), Files),
   26    doc_latex(Files, OutFile, Options),
   27    !.
   28
   29latex_for_pack_(Pack, File) :-
   30    md(Spec),
   31    absolute_file_name(Spec, File, [extensions([md]), relative_to(Pack)]).
   32latex_for_pack_(Pack, File) :-
   33    directory_member(Pack, File0, [extensions([md]), recursive(true)]),
   34    absolute_file_name(File0, File),
   35    file_base_name(File, Name),
   36    file_name_extension(Base, md, Name),
   37    \+ md(Base).
   38latex_for_pack_(Pack, File) :-
   39    absolute_file_name(Pack/prolog, Absolute),
   40    directory_member(Absolute, File, [file_type(prolog), recursive(true)]),
   41    doc_file_objects(File, _, Objects, FileOptions, []),
   42    (   Objects = [_|_]
   43    ->  true
   44    ;   member(file(_, _), FileOptions)
   45    ).
   46
   47md(readme).
   48md(changelog).
   49
   50pack_file(Spec, File) :-
   51    absolute_file_name(Spec, Absolute),
   52    absolute_directory(Absolute, Directory),
   53    absolute_file_name(pack, File, [ file_type(prolog),
   54                                     relative_to(Directory),
   55                                     access(read),
   56                                     file_errors(fail)
   57                                   ])