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_process,
  37          [ doc_comment/4,              % ?Object, ?Pos, ?Summary, ?Comment
  38            doc_file_has_comments/1,    % +File
  39            is_structured_comment/2,    % +Comment, -Prefixes
  40            parse_comment/3,            % +Comment, +FilePos, -Parsed
  41            process_comments/3,         % +Comments, +StartTermPos, +File
  42            doc_file_name/3             % +Source, -Doc, +Options
  43          ]).
  44
  45:- dynamic   user:file_search_path/2.
  46:- multifile user:file_search_path/2.
  47
  48user:file_search_path(pldoc, library(pldoc)).
  49
  50:- load_files([ pldoc(doc_register),
  51                pldoc(doc_modes),
  52                pldoc(doc_wiki),
  53                library(debug),
  54                library(option),
  55                library(lists),
  56                library(apply),
  57                library(operators),
  58                library(prolog_source)
  59              ],
  60              [ silent(true),
  61                if(not_loaded)
  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%!  doc_comment(?Objects, -Pos,
 211%!              -Summary:string, -Comment:string) is nondet.
 212%
 213%   True if Comment is the  comment   describing  object. Comment is
 214%   returned as a string object  containing   the  original from the
 215%   source-code.  Object is one of
 216%
 217%           * Name/Arity
 218%           Predicate indicator
 219%
 220%           * Name//Arity
 221%           DCG rule indicator.  Same as Name/Arity+2
 222%
 223%           * module(ModuleTitle)
 224%           Comment appearing in a module.
 225%
 226%   If Object is  unbound  and  multiple   objects  share  the  same
 227%   description, Object is unified with a   list  of terms described
 228%   above.
 229%
 230%   @param Summary  First sentence.  Normalised spacing.
 231%   @param Comment  Comment string from the source-code (untranslated)
 232
 233doc_comment(Object, Pos, Summary, Comment) :-
 234    var(Object),
 235    !,
 236    locally_defined(M:'$pldoc'/4),
 237    M:'$pldoc'(Obj, Pos, Summary, Comment),
 238    qualify(M, Obj, Object0),
 239    (   locally_defined(M:'$pldoc_link'/2),
 240        findall(L, M:'$pldoc_link'(L, Obj), Ls), Ls \== []
 241    ->  maplist(qualify(M), Ls, QLs),
 242        Object = [Object0|QLs]
 243    ;   Object = Object0
 244    ).
 245doc_comment(M:Object, Pos, Summary, Comment) :-
 246    !,
 247    locally_defined(M:'$pldoc'/4),
 248    (   M:'$pldoc'(Object, Pos, Summary, Comment)
 249    ;   locally_defined(M:'$pldoc_link'/2),
 250        M:'$pldoc_link'(Object, Obj2),
 251        M:'$pldoc'(Obj2, Pos, Summary, Comment)
 252    ).
 253doc_comment(Name/Arity, Pos, Summary, Comment) :-
 254    system_module(M),
 255    doc_comment(M:Name/Arity, Pos, Summary, Comment).
 256
 257
 258locally_defined(M:Name/Arity) :-
 259    current_module(M),
 260    current_predicate(M:Name/Arity),
 261    functor(Head, Name, Arity),
 262    \+ predicate_property(M:Head, imported_from(_)).
 263
 264
 265qualify(M, H, H) :- system_module(M), !.
 266qualify(M, H, H) :- sub_atom(M, 0, _, _, $), !.
 267qualify(M, H, M:H).
 268
 269system_module(user).
 270system_module(system).
 271
 272
 273%       Make the summary available to external tools on plugin basis.
 274
 275prolog:predicate_summary(PI, Summary) :-
 276    doc_comment(PI, _, Summary, _).
 277
 278
 279                 /*******************************
 280                 *      CALL-BACK COLLECT       *
 281                 *******************************/
 282
 283%!  process_comments(+Comments:list, +TermPos, +File) is det.
 284%
 285%   Processes comments returned by read_term/3 using the =comments=
 286%   option.  It creates clauses of the form
 287%
 288%           * '$mode'(Head, Det)
 289%           * '$pldoc'(Id, Pos, Summary, Comment)
 290%           * '$pldoc_link'(Id0, Id)
 291%
 292%   where Id is one of
 293%
 294%           * module(Title)
 295%           Generated from /** <module> Title */
 296%           * Name/Arity
 297%           Generated from Name(Arg, ...)
 298%           * Name//Arity
 299%           Generated from Name(Arg, ...)//
 300%
 301%   @param Comments is a list Pos-Comment returned by read_term/3
 302%   @param TermPos is the start-location of the actual term
 303%   @param File is the file that is being loaded.
 304
 305process_comments([], _, _).
 306process_comments([Pos-Comment|T], TermPos, File) :-
 307    (   Pos @> TermPos              % comments inside term
 308    ->  true
 309    ;   process_comment(Pos, Comment, File),
 310        process_comments(T, TermPos, File)
 311    ).
 312
 313process_comment(Pos, Comment, File) :-
 314    is_structured_comment(Comment, Prefixes, Style),
 315    !,
 316    stream_position_data(line_count, Pos, Line),
 317    FilePos = File:Line,
 318    process_structured_comment(FilePos, Comment, Prefixes, Style).
 319process_comment(_, _, _).
 320
 321%!  parse_comment(+Comment, +FilePos, -Parsed) is semidet.
 322%
 323%   True when Comment is a  structured   comment  and  Parsed is its
 324%   parsed representation. Parsed is a list of the following terms:
 325%
 326%     * section(Id, Title, Comment)
 327%     Generated from /** <module> Title Comment */ comments.
 328%     * predicate(PI, Summary, Comment)
 329%     Comment for predicate PI
 330%     * link(FromPI, ToPI)
 331%     Indicate that FromPI shares its comment with ToPI.  The actual
 332%     comment is in ToPI.
 333%     * mode(Head, Determinism)
 334%     Mode declaration.  Head is a term with Mode(Type) terms and
 335%     Determinism describes the associated determinism (=det=,
 336%     etc.).
 337
 338parse_comment(Comment, FilePos, Parsed) :-
 339    is_structured_comment(Comment, Prefixes),
 340    !,
 341    compile_comment(Comment, FilePos, Prefixes, Parsed).
 342
 343
 344%!  process_structured_comment(+FilePos,
 345%!                             +Comment:string,
 346%!                             +Prefixed:list,
 347%!                             +Style) is det.
 348%
 349%   Proccess a structured comment, adding the documentation facts to
 350%   the database. This predicate verifies that   the comment has not
 351%   already been loaded.
 352%
 353%   @tbd Note that as of version 7.3.12   clauses  from a file being
 354%   reloaded are not wiped before  the   reloading  and therefore we
 355%   cannot test the clause while  reloading   a  file. Ultimately we
 356%   need a better test for this.
 357
 358process_structured_comment(FilePos, Comment, _, _) :- % already processed
 359    prolog_load_context(module, M),
 360    locally_defined(M:'$pldoc'/4),
 361    catch(M:'$pldoc'(_, FilePos, _, Comment), _, fail),
 362    (   FilePos = File:_,
 363        source_file_property(File, reloading)
 364    ->  debug(pldoc(reload), 'Reloading ~q', [FilePos]),
 365        fail
 366    ;   true
 367    ),
 368    !.
 369process_structured_comment(FilePos, Comment, Prefixes, Style) :-
 370    catch(compile_comment(Comment, FilePos, Prefixes, Compiled), E,
 371          comment_warning(Style, E)),
 372    maplist(store_comment(FilePos), Compiled).
 373process_structured_comment(FilePos, Comment, _Prefixes, Style) :-
 374    comment_style_warning_level(Style, Level),
 375    print_message(Level,
 376                  pldoc(invalid_comment(FilePos, Comment))).
 377
 378comment_style_warning_level(percent_percent, silent) :- !.
 379comment_style_warning_level(_, warning).
 380
 381%!  comment_warning(+Style, +Error) is failure.
 382%
 383%   Print a warning  on  structured  comments   that  could  not  be
 384%   processed. Since the recommended magic   sequence is now =|%!|=,
 385%   we remain silent about comments that start with =|%%|=.
 386
 387comment_warning(Style, E) :-
 388    comment_style_warning_level(Style, Level),
 389    print_message(Level, E),
 390    fail.
 391
 392%!  compile_comment(+Comment, +FilePos, +Prefixes, -Compiled) is semidet.
 393%
 394%   Compile structured Comment into a list   of  terms that describe
 395%   the comment.
 396%
 397%   @see parse_comment/3 for the terms in Compiled.
 398
 399compile_comment(Comment, FilePos, Prefixes, Compiled) :-
 400    string_codes(Comment, CommentCodes),
 401    indented_lines(CommentCodes, Prefixes, Lines),
 402    (   section_comment_header(Lines, Header, _RestLines)
 403    ->  Header = \section(Type, Title),
 404        Id =.. [Type,Title],
 405        Compiled = [section(Id, Title, Comment)]
 406    ;   prolog_load_context(module, Module),
 407        process_modes(Lines, Module, FilePos, Modes, _, RestLines)
 408    ->  maplist(compile_mode, Modes, ModeDecls),
 409        modes_to_predicate_indicators(Modes, AllPIs),
 410        decl_module(AllPIs, M, [PI0|PIs]),
 411        maplist(link_term(M:PI0), PIs, Links),
 412        summary_from_lines(RestLines, Codes),
 413        string_codes(Summary, Codes),
 414        append([ ModeDecls,
 415                 [ predicate(M:PI0, Summary, Comment) ],
 416                 Links
 417               ], Compiled)
 418    ),
 419    !.
 420
 421
 422store_comment(Pos, section(Id, Title, Comment)) :-
 423    !,
 424    compile_clause('$pldoc'(Id, Pos, Title, Comment), Pos).
 425store_comment(Pos, predicate(M:PI, Summary, Comment)) :-
 426    !,
 427    compile_clause(M:'$pldoc'(PI, Pos, Summary, Comment), Pos).
 428store_comment(Pos, link(PI, M:PI0)) :-
 429    !,
 430    compile_clause(M:'$pldoc_link'(PI, PI0), Pos).
 431store_comment(Pos, mode(Head, Det)) :-
 432    !,
 433    compile_clause('$mode'(Head, Det), Pos).
 434store_comment(_, Term) :-
 435    type_error(pldoc_term, Term).
 436
 437link_term(To, From, link(From,To)).
 438
 439decl_module([], M, []) :-
 440    (   var(M)
 441    ->  prolog_load_context(module, M)
 442    ;   true
 443    ).
 444decl_module([H0|T0], M, [H|T]) :-
 445    (   H0 = M1:H
 446    ->  M = M1
 447    ;   H = H0
 448    ),
 449    decl_module(T0, M, T).
 450
 451
 452                 /*******************************
 453                 *           MESSAGES           *
 454                 *******************************/
 455
 456:- multifile
 457    prolog:message//1.
 458
 459prolog:message(pldoc(invalid_comment(File:Line, Comment))) -->
 460    [ '~w:~d: PlDoc: failed to process structured comment:~n~s~n'-
 461            [File, Line, Comment]
 462    ].