View source with formatted 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-2020, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    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_process,
   38          [ doc_comment/4,              % ?Object, ?Pos, ?Summary, ?Comment
   39            doc_file_has_comments/1,    % +File
   40            is_structured_comment/2,    % +Comment, -Prefixes
   41            parse_comment/3,            % +Comment, +FilePos, -Parsed
   42            comment_modes/2,            % +Comment, -Synopsis
   43            process_comments/3,         % +Comments, +StartTermPos, +File
   44            doc_file_name/3,            % +Source, -Doc, +Options
   45            doc_clean/1                 % +Module
   46          ]).   47
   48:- dynamic   user:file_search_path/2.   49:- multifile user:file_search_path/2.   50
   51user:file_search_path(pldoc, library(pldoc)).
   52
   53:- use_module(pldoc(doc_register)).   54:- use_module(pldoc(doc_modes)).   55:- use_module(pldoc(doc_wiki)).   56:- use_module(library(debug)).   57:- use_module(library(option)).   58:- use_module(library(lists)).   59:- use_module(library(apply)).   60:- use_module(library(operators)).   61:- use_module(library(prolog_source)).   62
   63
   64/** <module> Process source documentation
   65The pldoc module processes structured comments in Prolog source files into
   66well formatted HTML documents.
   67
   68@author  Jan Wielemaker
   69@license GPL
   70*/
   71
   72:- predicate_options(doc_file_name/3, 3,
   73                     [ format(oneof([html,tex]))
   74                     ]).   75
   76%!  prolog:predicate_summary(+PI, -Summary) is semidet.
   77%
   78%   Provide    predicate    summaries    to     the    XPCE    class
   79%   =prolog_predicate=, used by the IDE tools.
   80
   81:- multifile
   82    prolog:predicate_summary/2.     % ?PI, -Summary
   83
   84
   85%!  is_structured_comment(+Comment:string,
   86%!                        -Prefixes:list(codes)) is semidet.
   87%
   88%   True if Comment is a structured comment that should use Prefixes
   89%   to extract the plain text using indented_lines/3.
   90
   91is_structured_comment(Comment, Prefixes) :-
   92    is_structured_comment(Comment, Prefixes, _Style).
   93
   94is_structured_comment(_Pos-Comment, Prefixes, Style) :-
   95    !,
   96    is_structured_comment(Comment, Prefixes, Style).
   97is_structured_comment(Comment, Prefixes, Style) :-
   98    is_list(Comment),
   99    !,
  100    (   phrase(structured_comment(Prefixes, Style), Comment, _)
  101    ->  true
  102    ).
  103is_structured_comment(Comment, Prefixes, Style) :-
  104    atom_string(CommentA, Comment),
  105    structured_command_start(Start, Prefixes, Style),
  106    sub_atom(CommentA, 0, Len, _, Start),
  107    !,
  108    sub_atom(CommentA, Len, 1, _, Space),
  109    char_type(Space, space),
  110    (   Style == block
  111    ->  true
  112    ;   \+ blanks_to_nl(CommentA)
  113    ).
  114
  115structured_command_start('%%',  ["%"], percent_percent).        % Deprecated
  116structured_command_start('%!',  ["%"], percent_bang).           % New style
  117structured_command_start('/**', ["/**", " *"], block).          % block
  118
  119blanks_to_nl(CommentA) :-
  120    sub_atom(CommentA, At, 1, _, Char),
  121    At >= 2,
  122    (   char_type(Char, end_of_line)
  123    ->  !
  124    ;   (   char_type(Char, space)
  125        ;   Char == '%'
  126        )
  127    ->  fail
  128    ;   !, fail
  129    ).
  130blanks_to_nl(_).
  131
  132%!  structured_comment(-Prefixes:list(codes), -Style) is semidet.
  133%
  134%   Grammar rule version of the above.  Avoids the need for
  135%   conversion.
  136
  137structured_comment(["%"], percent_percent) -->
  138    "%%", space,
  139    \+ separator_line.
  140structured_comment(["%"], percent_bang) -->
  141    "%!", space.
  142structured_comment(Prefixes, block) -->
  143    "/**", space,
  144    { Prefixes = ["/**", " *"]
  145    }.
  146
  147space -->
  148    [H],
  149    { code_type(H, space) }.
  150
  151%!  separator_line// is semidet.
  152%
  153%   Matches a line like %% SWI or %%%%%%%%%%%%%%%%%%%%%%%%%, etc.
  154
  155separator_line -->
  156    string(S), "\n",
  157    !,
  158    {   maplist(blank_or_percent, S)
  159    ;   contains(S, " SWI ")
  160    ;   contains(S, " SICStus ")
  161    ;   contains(S, " Mats ")
  162    }.
  163
  164string([]) --> [].
  165string([H|T]) --> [H], string(T).
  166
  167blank_or_percent(0'%) :- !.
  168blank_or_percent(C) :-
  169    code_type(C, space).
  170
  171contains(Haystack, Needle) :-
  172    string_codes(Needle, NeedleCodes),
  173    append(_, Start, Haystack),
  174    append(NeedleCodes, _, Start),
  175    !.
  176
  177
  178%!  doc_file_name(+Source:atom, -Doc:atom, +Options:list) is det.
  179%
  180%   Doc is the name of the file for documenting Source.
  181%
  182%   @param Source   Prolog source to be documented
  183%   @param Doc      the name of the file documenting Source.
  184%   @param Options  Option list:
  185%
  186%                   * format(+Format)
  187%                   Output format.  One of =html= or =tex=
  188%
  189%   @error  permission_error(overwrite, Source)
  190
  191doc_file_name(Source, Doc, Options) :-
  192    option(format(Format), Options, html),
  193    file_name_extension(Base, _Ext, Source),
  194    file_name_extension(Base, Format, Doc),
  195    (   Source == Doc
  196    ->  throw(error(permission_error(overwrite, Source), _))
  197    ;   true
  198    ).
  199
  200%!  doc_file_has_comments(+Source:atom) is semidet.
  201%
  202%   True if we have loaded comments from Source.
  203
  204doc_file_has_comments(Source) :-
  205    source_file_property(Source, module(M)),
  206    locally_defined(M:'$pldoc'/4),
  207    M:'$pldoc'(_, _, _, _),
  208    !.
  209
  210
  211%!  doc_comment(?Objects, -Pos,
  212%!              -Summary:string, -Comment:string) is nondet.
  213%
  214%   True if Comment is the  comment   describing  object. Comment is
  215%   returned as a string object  containing   the  original from the
  216%   source-code.  Object is one of
  217%
  218%           * Name/Arity
  219%           Predicate indicator
  220%
  221%           * Name//Arity
  222%           DCG rule indicator.  Same as Name/Arity+2
  223%
  224%           * module(ModuleTitle)
  225%           Comment appearing in a module.
  226%
  227%   If Object is  unbound  and  multiple   objects  share  the  same
  228%   description, Object is unified with a   list  of terms described
  229%   above.
  230%
  231%   @param Summary  First sentence.  Normalised spacing.
  232%   @param Comment  Comment string from the source-code (untranslated)
  233
  234doc_comment(Object, Pos, Summary, Comment) :-
  235    var(Object),
  236    !,
  237    locally_defined(M:'$pldoc'/4),
  238    M:'$pldoc'(Obj, Pos, Summary, Comment),
  239    qualify(M, Obj, Object0),
  240    (   locally_defined(M:'$pldoc_link'/2),
  241        findall(L, M:'$pldoc_link'(L, Obj), Ls), Ls \== []
  242    ->  maplist(qualify(M), Ls, QLs),
  243        Object = [Object0|QLs]
  244    ;   Object = Object0
  245    ).
  246doc_comment(M:Object, Pos, Summary, Comment) :-
  247    !,
  248    locally_defined(M:'$pldoc'/4),
  249    (   M:'$pldoc'(Object, Pos, Summary, Comment)
  250    ;   locally_defined(M:'$pldoc_link'/2),
  251        M:'$pldoc_link'(Object, Obj2),
  252        M:'$pldoc'(Obj2, Pos, Summary, Comment)
  253    ).
  254doc_comment(Name/Arity, Pos, Summary, Comment) :-
  255    system_module(M),
  256    doc_comment(M:Name/Arity, Pos, Summary, Comment).
  257
  258
  259locally_defined(M:Name/Arity) :-
  260    current_predicate(M:Name/Arity),
  261    functor(Head, Name, Arity),
  262%   \+ predicate_property(M:Head, imported_from(_)).
  263    \+ '$get_predicate_attribute'(M:Head, imported, _).
  264
  265
  266qualify(M, H, H) :- system_module(M), !.
  267qualify(M, H, H) :- sub_atom(M, 0, _, _, $), !.
  268qualify(M, H, M:H).
  269
  270system_module(user).
  271system_module(system).
  272
  273
  274%       Make the summary available to external tools on plugin basis.
  275
  276prolog:predicate_summary(PI, Summary) :-
  277    doc_comment(PI, _, Summary, _).
  278
  279
  280                 /*******************************
  281                 *      CALL-BACK COLLECT       *
  282                 *******************************/
  283
  284%!  process_comments(+Comments:list, +TermPos, +File) is det.
  285%
  286%   Processes comments returned by read_term/3 using the =comments=
  287%   option.  It creates clauses of the form
  288%
  289%           * '$mode'(Head, Det)
  290%           * '$pldoc'(Id, Pos, Summary, Comment)
  291%           * '$pldoc_link'(Id0, Id)
  292%
  293%   where Id is one of
  294%
  295%           * module(Title)
  296%           Generated from /** <module> Title */
  297%           * Name/Arity
  298%           Generated from Name(Arg, ...)
  299%           * Name//Arity
  300%           Generated from Name(Arg, ...)//
  301%
  302%   @param Comments is a list Pos-Comment returned by read_term/3
  303%   @param TermPos is the start-location of the actual term
  304%   @param File is the file that is being loaded.
  305
  306process_comments([], _, _).
  307process_comments([Pos-Comment|T], TermPos, File) :-
  308    (   Pos @> TermPos              % comments inside term
  309    ->  true
  310    ;   process_comment(Pos, Comment, File),
  311        process_comments(T, TermPos, File)
  312    ).
  313
  314process_comment(Pos, Comment, File) :-
  315    is_structured_comment(Comment, Prefixes, Style),
  316    !,
  317    stream_position_data(line_count, Pos, Line),
  318    FilePos = File:Line,
  319    process_structured_comment(FilePos, Comment, Prefixes, Style).
  320process_comment(_, _, _).
  321
  322%!  parse_comment(+Comment, +FilePos, -Parsed) is semidet.
  323%
  324%   True when Comment is a  structured   comment  and  Parsed is its
  325%   parsed representation. Parsed is a list of the following terms:
  326%
  327%     * section(Id, Title, Comment)
  328%     Generated from /** <module> Title Comment */ comments.
  329%     * predicate(PI, Summary, Comment)
  330%     Comment for predicate PI
  331%     * link(FromPI, ToPI)
  332%     Indicate that FromPI shares its comment with ToPI.  The actual
  333%     comment is in ToPI.
  334%     * mode(Head, Determinism)
  335%     Mode declaration.  Head is a term with Mode(Type) terms and
  336%     Determinism describes the associated determinism (=det=,
  337%     etc.).
  338
  339parse_comment(Comment, FilePos, Parsed) :-
  340    is_structured_comment(Comment, Prefixes),
  341    !,
  342    compile_comment(Comment, FilePos, Prefixes, Parsed).
  343
  344
  345%!  comment_modes(+Comment, -Modes:list) is semidet.
  346
  347comment_modes(Comment, Modes) :-
  348    is_structured_comment(Comment, Prefixes),
  349    string_codes(Comment, CommentCodes),
  350    indented_lines(CommentCodes, Prefixes, Lines),
  351    (   prolog_load_context(module, Module)
  352    ->  true
  353    ;   Module = user
  354    ),
  355    process_modes(Lines, Module, dummy:0, Modes0, _Vars, _),
  356    maplist(bind_mode, Modes0, Modes).
  357
  358bind_mode(mode(Mode, Bindings), Mode) :-
  359    maplist(bind_var, Bindings).
  360
  361bind_var(Name=Name).
  362
  363%!  process_structured_comment(+FilePos,
  364%!                             +Comment:string,
  365%!                             +Prefixed:list,
  366%!                             +Style) is det.
  367%
  368%   Proccess a structured comment, adding the documentation facts to
  369%   the database. This predicate verifies that   the comment has not
  370%   already been loaded.
  371%
  372%   @tbd Note that as of version 7.3.12   clauses  from a file being
  373%   reloaded are not wiped before  the   reloading  and therefore we
  374%   cannot test the clause while  reloading   a  file. Ultimately we
  375%   need a better test for this.
  376
  377process_structured_comment(FilePos, Comment, _, _) :- % already processed
  378    prolog_load_context(module, M),
  379    locally_defined(M:'$pldoc'/4),
  380    catch(M:'$pldoc'(_, FilePos, _, Comment), _, fail),
  381    (   FilePos = File:_,
  382        source_file_property(File, reloading)
  383    ->  debug(pldoc(reload), 'Reloading ~q', [FilePos]),
  384        fail
  385    ;   true
  386    ),
  387    !.
  388process_structured_comment(FilePos, Comment, Prefixes, Style) :-
  389    catch(compile_comment(Comment, FilePos, Prefixes, Compiled), E,
  390          comment_warning(Style, E)),
  391    maplist(store_comment(FilePos), Compiled).
  392process_structured_comment(FilePos, Comment, _Prefixes, Style) :-
  393    comment_style_warning_level(Style, Level),
  394    print_message(Level,
  395                  pldoc(invalid_comment(FilePos, Comment))).
  396
  397comment_style_warning_level(percent_percent, silent) :- !.
  398comment_style_warning_level(_, warning).
  399
  400%!  comment_warning(+Style, +Error) is failure.
  401%
  402%   Print a warning  on  structured  comments   that  could  not  be
  403%   processed. Since the recommended magic   sequence is now =|%!|=,
  404%   we remain silent about comments that start with =|%%|=.
  405
  406comment_warning(Style, E) :-
  407    comment_style_warning_level(Style, Level),
  408    print_message(Level, E),
  409    fail.
  410
  411%!  compile_comment(+Comment, +FilePos, +Prefixes, -Compiled) is semidet.
  412%
  413%   Compile structured Comment into a list   of  terms that describe
  414%   the comment.
  415%
  416%   @see parse_comment/3 for the terms in Compiled.
  417
  418compile_comment(Comment, FilePos, Prefixes, Compiled) :-
  419    string_codes(Comment, CommentCodes),
  420    indented_lines(CommentCodes, Prefixes, Lines),
  421    (   section_comment_header(Lines, Header, _RestLines)
  422    ->  Header = \section(Type, Title),
  423        Id =.. [Type,Title],
  424        Compiled = [section(Id, Title, Comment)]
  425    ;   prolog_load_context(module, Module),
  426        process_modes(Lines, Module, FilePos, Modes, _, RestLines)
  427    ->  maplist(compile_mode, Modes, ModeDecls),
  428        modes_to_predicate_indicators(Modes, AllPIs),
  429        decl_module(AllPIs, M, [PI0|PIs]),
  430        maplist(link_term(M:PI0), PIs, Links),
  431        summary_from_lines(RestLines, Codes),
  432        string_codes(Summary, Codes),
  433        append([ ModeDecls,
  434                 [ predicate(M:PI0, Summary, Comment) ],
  435                 Links
  436               ], Compiled)
  437    ),
  438    !.
  439
  440
  441store_comment(Pos, section(Id, Title, Comment)) :-
  442    !,
  443    compile_clause('$pldoc'(Id, Pos, Title, Comment), Pos).
  444store_comment(Pos, predicate(M:PI, Summary, Comment)) :-
  445    !,
  446    compile_clause(M:'$pldoc'(PI, Pos, Summary, Comment), Pos).
  447store_comment(Pos, link(PI, M:PI0)) :-
  448    !,
  449    compile_clause(M:'$pldoc_link'(PI, PI0), Pos).
  450store_comment(Pos, mode(Head, Det)) :-
  451    !,
  452    compile_clause('$mode'(Head, Det), Pos).
  453store_comment(_, Term) :-
  454    type_error(pldoc_term, Term).
  455
  456link_term(To, From, link(From,To)).
  457
  458decl_module([], M, []) :-
  459    (   var(M)
  460    ->  prolog_load_context(module, M)
  461    ;   true
  462    ).
  463decl_module([H0|T0], M, [H|T]) :-
  464    (   H0 = M1:H
  465    ->  M = M1
  466    ;   H = H0
  467    ),
  468    decl_module(T0, M, T).
  469
  470%!  doc_clean(+Module) is det.
  471%
  472%   Clean documentation for Module.
  473
  474doc_clean(Module) :-
  475    abolish(Module:'$mode'/2),
  476    abolish(Module:'$pldoc'/4),
  477    abolish(Module:'$pldoc_link'/2).
  478
  479
  480                 /*******************************
  481                 *           MESSAGES           *
  482                 *******************************/
  483
  484:- multifile
  485    prolog:message//1.  486
  487prolog:message(pldoc(invalid_comment(File:Line, Comment))) -->
  488    [ url(File:Line), ': PlDoc: failed to process structured comment:~n~s~n'-
  489            [Comment]
  490    ]