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-2014, 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_index,
   37          [ doc_for_dir/2,              % +Dir, +Options
   38            dir_index//2,               % +Dir, +Options, //
   39            object_summaries//3,        % +Objs, +Section, +Options, //
   40            file_index_header//2,       % +File, +Options, //
   41            doc_links//2,               % +Directory, +Options, //
   42            doc_file_href/2,            % +File, -HREF
   43            places_menu//1,             % +Dir, //
   44            source_directory/1          % ?Directory
   45          ]).   46:- use_module(doc_process).   47:- use_module(doc_html).   48:- use_module(doc_wiki).   49:- use_module(doc_search).   50:- use_module(doc_util).   51:- use_module(library(http/http_dispatch)).   52:- use_module(library(http/html_write)).   53:- use_module(library(http/html_head)).   54:- use_module(library(readutil)).   55:- use_module(library(url)).   56:- use_module(library(option)).   57:- use_module(library(lists)).   58:- use_module(library(doc_http)).   59:- include(hooks).

Create indexes

*/

   64:- predicate_options(dir_index//2, 2,
   65                     [ directory(atom),
   66                       edit(boolean),
   67                       files(list),
   68                       members(list),
   69                       qualify(boolean),
   70                       title(atom),
   71                       if(oneof([true,loaded])),
   72                       recursive(boolean),
   73                       secref_style(oneof([number, title, number_title])),
   74                       pass_to(doc_links/4, 2)
   75                     ]).   76:- predicate_options(doc_links//2, 2,
   77                     [ files(list),
   78                       pass_to(pldoc_search:search_form/3, 1)
   79                     ]).   80:- predicate_options(file_index_header//2, 2,
   81                     [ directory(any),
   82                       files(list),
   83                       qualify(boolean),
   84                       secref_style(oneof([number, title, number_title])),
   85                       pass_to(pldoc_html:edit_button/4, 2),
   86                       pass_to(pldoc_html:source_button/4, 2)
   87                     ]).   88:- predicate_options(object_summaries//3, 3,
   89                     [ edit(boolean),
   90                       files(list),
   91                       module(atom),
   92                       public(list),
   93                       qualify(boolean),
   94                       secref_style(oneof([number, title, number_title]))
   95                     ]).   96:- predicate_options(doc_for_dir/2, 2, [pass_to(dir_index/4, 2)]).
 doc_for_dir(+Dir, +Options) is det
Write summary index for all files in Dir to Out. The result consists of the README file (if any), a table holding with links to objects and summary sentences and finaly the TODO file (if any).
  105doc_for_dir(DirSpec, Options) :-
  106    absolute_file_name(DirSpec,
  107                       [ file_type(directory),
  108                         access(read)
  109                       ],
  110                       Dir),
  111    (   option(title(Title), Options)
  112    ->  true
  113    ;   file_base_name(Dir, Title)
  114    ),
  115    doc_write_page(
  116        pldoc(dir_index),
  117        title(Title),
  118        \dir_index(Dir, Options),
  119        Options).
  120
  121:- html_meta doc_write_page(+, html, html, +).  122
  123doc_write_page(Style, Head, Body, Options) :-
  124    option(files(_), Options),
  125    !,
  126    phrase(page(Style, Head, Body), HTML),
  127    print_html(HTML).
  128doc_write_page(Style, Head, Body, _) :-
  129    reply_html_page(Style, Head, Body).
 dir_index(+Dir, +Options)//
Create an index for all Prolog files appearing in Dir or in any directory contained in Dir. Options:
members(+Members)
Documented members. See doc_files.pl
title(+Title)
Title to use for the index page
  142dir_index(Dir, Options) -->
  143    { dir_source_files(Dir, Files0, Options),
  144      sort(Files0, Files),
  145      maplist(ensure_doc_objects, Files),
  146      directory_file_path(Dir, 'index.html', File),
  147      b_setval(pldoc_file, File)    % for predref
  148    },
  149    html([ \doc_resources(Options),
  150           \doc_links(Dir, Options),
  151           \dir_header(Dir, Options),
  152           \subdir_links(Dir, Options),
  153           h2(class([wiki,plfiles]), 'Prolog files'),
  154           table(class(summary),
  155                 \file_indices(Files, [directory(Dir)|Options])),
  156           \dir_footer(Dir, Options)
  157         ]).
 dir_source_files(+Dir, -Files, +Options) is det
Create a list of source-files to be documented as part of Dir.
  163dir_source_files(_, Files, Options) :-
  164    option(members(Members), Options),
  165    !,
  166    findall(F, member(file(F,_Doc), Members), Files).
  167dir_source_files(Dir, Files, Options) :-
  168    directory_source_files(Dir, Files, Options).
 subdir_links(+Dir, +Options)// is det
Create links to subdirectories
  174subdir_links(Dir, Options) -->
  175    { option(members(Members), Options),
  176      findall(SubDir, member(directory(SubDir, _, _, _), Members), SubDirs),
  177      SubDirs \== []
  178    },
  179    html([ h2(class([wiki,subdirs]), 'Sub directories'),
  180           table(class(subdirs),
  181                 \subdir_link_rows(SubDirs, Dir))
  182         ]).
  183subdir_links(_, _) --> [].
  184
  185subdir_link_rows([], _) --> [].
  186subdir_link_rows([H|T], Dir) -->
  187    subdir_link_row(H, Dir),
  188    subdir_link_rows(T, Dir).
  189
  190subdir_link_row(Dir, From) -->
  191    { directory_file_path(Dir, 'index.html', Index),
  192      relative_file_name(Index, From, Link),
  193      file_base_name(Dir, Base)
  194    },
  195    html(tr(td(a([class(subdir), href(Link)], ['[dir] ', Base])))).
 dir_header(+Dir, +Options)// is det
Create header for directory. Options:
readme(File)
Include File as introduction to the directory header.
  204dir_header(Dir, Options) -->
  205    wiki_file(Dir, readme, Options),
  206    !.
  207dir_header(Dir, Options) -->
  208    { (   option(title(Title), Options)
  209      ->  true
  210      ;   file_base_name(Dir, Title)
  211      )
  212    },
  213    html(h1(class=dir, Title)).
 dir_footer(+Dir, +Options)// is det
Create footer for directory. The footer contains the TODO file if provided. Options:
todo(File)
Include File as TODO file in the footer.
  223dir_footer(Dir, Options) -->
  224    wiki_file(Dir, todo, Options),
  225    !.
  226dir_footer(_, _) -->
  227    [].
 wiki_file(+Dir, +Type, +Options)// is semidet
Include text from a Wiki text-file.
  233wiki_file(Dir, Type, Options) -->
  234    { (   Opt =.. [Type,WikiFile],
  235          option(Opt, Options)
  236      ->  true
  237      ;   directory_files(Dir, Files),
  238          member(File, Files),
  239          wiki_file_type(Type, Pattern),
  240          downcase_atom(File, Pattern),
  241          directory_file_path(Dir, File, WikiFile)
  242      ),
  243      access_file(WikiFile, read),
  244      !,
  245      read_file_to_codes(WikiFile, String, []),
  246      wiki_codes_to_dom(String, [], DOM)
  247    },
  248    pldoc_html:html(DOM).
 wiki_file_type(+Category, -File) is nondet
Declare file pattern names that are included for README and TODO for a directory. Files are matched case-insensitively.
  255wiki_file_type(readme, 'readme').
  256wiki_file_type(readme, 'readme.md').
  257wiki_file_type(readme, 'readme.txt').
  258wiki_file_type(todo,   'todo').
  259wiki_file_type(todo,   'todo.md').
  260wiki_file_type(todo,   'todo.txt').
 file_indices(+Files, +Options)// is det
Provide a file-by-file index of the contents of each member of Files.
  267file_indices([], _) -->
  268    [].
  269file_indices([H|T], Options) -->
  270    file_index(H, Options),
  271    file_indices(T, Options).
 file_index(+File, +Options)// is det
Create an index for File.
  277file_index(File, Options) -->
  278    { doc_summaries(File, Objs0),
  279      module_info(File, ModuleOptions, Options),
  280      doc_hide_private(Objs0, Objs1, ModuleOptions),
  281      sort(Objs1, Objs)
  282    },
  283    html([ \file_index_header(File, Options)
  284         | \object_summaries(Objs, File, ModuleOptions)
  285         ]).
  286
  287doc_summaries(File, Objects) :-
  288    xref_current_source(FileSpec),
  289    xref_option(FileSpec, comments(collect)),
  290    !,
  291    Pos = File:0,
  292    findall(doc(Obj,Pos,Summary),
  293            xref_doc_summary(Obj, Pos, Summary), Objects).
  294doc_summaries(File, Objects) :-
  295    Pos = File:_Line,
  296    findall(doc(Obj,Pos,Summary),
  297            doc_comment(Obj, Pos, Summary, _), Objects).
  298
  299xref_doc_summary(M:Name/Arity, File:_, Summary) :-
  300    xref_comment(File, Head, Summary, _Comment),
  301    xref_module(File, Module),
  302    strip_module(Module:Head, M, Plain),
  303    functor(Plain, Name, Arity).
 file_index_header(+File, +Options)// is det
Create an entry in a summary-table for File.
  309file_index_header(File, Options) -->
  310    prolog:doc_file_index_header(File, Options),
  311    !.
  312file_index_header(File, Options) -->
  313    { (   option(directory(Dir), Options),
  314          directory_file_path(Dir, Label, File)
  315      ->  true
  316      ;   file_base_name(File, Label)
  317      ),
  318      doc_file_href(File, HREF, Options)
  319    },
  320    html(tr(th([colspan(3), class(file)],
  321               [ span(style('float:left'), a(href(HREF), Label)),
  322                 \file_module_title(File),
  323                 span(style('float:right'),
  324                      [ \source_button(File, Options),
  325                        \edit_button(File, Options)
  326                      ])
  327               ]))).
  328
  329file_module_title(File) -->
  330    { (   module_property(M, file(File))
  331      ;   xref_module(File, M)
  332      ),
  333      doc_comment(M:module(Title), _, _, _)
  334    },
  335    !,
  336    html([&(nbsp), ' -- ', Title]).
  337file_module_title(_) -->
  338    [].
 doc_file_href(+File, -HREF, +Options) is det
HREF is reference to documentation of File.
  345doc_file_href(File, HREF, Options) :-
  346    option(directory(Dir), Options),
  347    atom_concat(Dir, Local0, File),
  348    atom_concat(/, Local, Local0),
  349    !,
  350    (   option(files(Map), Options),        % generating files
  351        memberchk(file(File, DocFile), Map)
  352    ->  file_base_name(DocFile, HREF)
  353    ;   HREF = Local
  354    ).
  355doc_file_href(File, HREF, _) :-
  356    doc_file_href(File, HREF).
 doc_file_href(+Path, -HREF) is det
Create a /doc HREF from Path. There are some nasty things we should take care of.
  368doc_file_href(File0, HREF) :-
  369    insert_alias(File0, File),
  370    ensure_slash_start(File, SlashFile),
  371    http_location([path(SlashFile)], Escaped),
  372    http_location_by_id(pldoc_doc, DocRoot),
  373    atom_concat(DocRoot, Escaped, HREF).
 ensure_slash_start(+File0, -File) is det
Ensure File starts with a /. This maps C:/foobar into /C:/foobar, so our paths start with /doc/ again ...
  381ensure_slash_start(File, File) :-
  382    sub_atom(File, 0, _, _, /),
  383    !.
  384ensure_slash_start(File0, File) :-
  385    atom_concat(/, File0, File).
 object_summaries(+Objects, +Section, +Options)// is det
Create entries in a summary table for Objects.
  392object_summaries(Objects, Section, Options) -->
  393    { tag_pub_priv(Objects, Tagged, Options),
  394      keysort(Tagged, Ordered)
  395    },
  396    obj_summaries(Ordered, Section, Options).
  397
  398obj_summaries([], _, _) -->
  399    [].
  400obj_summaries([_Tag-H|T], Section, Options) -->
  401    object_summary(H, Section, Options),
  402    obj_summaries(T, Section, Options).
  403
  404tag_pub_priv([], [], _).
  405tag_pub_priv([H|T0], [Tag-H|T], Options) :-
  406    (   private(H, Options)
  407    ->  Tag = z_private
  408    ;   Tag = a_public
  409    ),
  410    tag_pub_priv(T0, T, Options).
 object_summary(+Object, +Section, +Options)// is det
Create a summary for Object. Summary consists of a link to the Object and a summary text as a table-row.
To be done
- Hacky interface. Do we demand Summary to be in Wiki?
  420object_summary(doc(Obj, _Pos, _Summary), wiki, Options) -->
  421    !,
  422    html(tr(class(wiki),
  423            [ td(colspan(3), \object_ref(Obj, Options))
  424            ])).
  425object_summary(doc(Obj, _Pos, Summary), _Section, Options) -->
  426    !,
  427    (   { string_codes(Summary, Codes),
  428          wiki_codes_to_dom(Codes, [], DOM0),
  429          strip_leading_par(DOM0, DOM),
  430          (   private(Obj, Options)
  431          ->  Class = private               % private definition
  432          ;   Class = public                % public definition
  433          )
  434        }
  435    ->  html(tr(class(Class),
  436                [ td(\object_ref(Obj, Options)),
  437                  td(class(summary), DOM),
  438                  td([align(right)],
  439                     span(style('white-space: nowrap'),
  440                          [ \object_source_button(Obj, Options),
  441                            \object_edit_button(Obj, Options)
  442                          ]))
  443                ]))
  444    ;   []
  445    ).
  446object_summary(Obj, Section, Options) -->
  447    { prolog:doc_object_summary(Obj, _Cat, Section, Summary)
  448    },
  449    !,
  450    object_summary(doc(Obj, _, Summary), Section, Options).
  451object_summary(_, _, _) -->
  452    [].
  453
  454
  455                 /*******************************
  456                 *          NAVIGATION          *
  457                 *******************************/
 doc_links(+Directory, +Options)// is det
Provide overview links and search facilities.
  463doc_links(_Directory, Options) -->
  464    { option(files(_), Options), !
  465    }.
  466doc_links(Directory, Options) -->
  467    prolog:doc_links(Directory, Options),
  468    !,
  469    { option(html_resources(Resoures), Options, pldoc) },
  470    html_requires(Resoures).
  471doc_links(Directory, Options) -->
  472    {   (   Directory == ''
  473        ->  working_directory(Dir, Dir)
  474        ;   Dir = Directory
  475        ),
  476        option(html_resources(Resoures), Options, pldoc)
  477    },
  478    html([ \html_requires(Resoures),
  479           div(class(navhdr),
  480               [ div(class(jump),
  481                      div([ \places_menu(Dir),
  482                            \plversion
  483                          ])),
  484                 div(class(search), \search_form(Options)),
  485                 br(clear(right))
  486               ])
  487         ]).
 version// is det
Prolog version
  494plversion -->
  495    { current_prolog_flag(version_data, swi(Major, Minor, Patch, _))
  496    },
  497    !,
  498    html(a([ class(prolog_version),
  499             href('http://www.swi-prolog.org')
  500           ],
  501           [' SWI-Prolog ', Major, '.', Minor, '.', Patch])).
  502
  503plversion -->
  504    { current_prolog_flag(version_data, yap(Major, Minor, Patch, _))
  505    },
  506    html(a([ class(prolog_version),
  507             href('http://www.dcc.fc.up.pt/~vsc')
  508           ],
  509           [' YAP ', Major, '.', Minor, '.', Patch])).
 places_menu(Current)// is det
Create a select menu with entries for all loaded directories
  516places_menu(Dir) -->
  517    prolog:doc_places_menu(Dir),
  518    !.
  519places_menu(Dir) -->
  520    { findall(D, source_directory(D), List),
  521      sort(List, Dirs)
  522    },
  523    html(form([ action(location_by_id(go_place))
  524              ],
  525              [ input([type(submit), value('Go')]),
  526                select(name(place),
  527                       \packs_source_dirs(Dirs, Dir))
  528              ])).
  529
  530packs_source_dirs(Dirs, Dir) -->
  531    packs_link,
  532    source_dirs(Dirs, Dir).
  533
  534source_dirs([], _) -->
  535    [].
  536source_dirs([H|T], WD) -->
  537    { (   H == WD
  538      ->  Attrs = [selected]
  539      ;   Attrs = []
  540      ),
  541      format(string(IndexFile), '~w/index.html', [H]),
  542      doc_file_href(IndexFile, HREF),
  543      format(string(Call), 'document.location=\'~w\';', [HREF])
  544    },
  545    html(option([onClick(Call)|Attrs], H)),
  546    source_dirs(T, WD).
  547
  548packs_link -->
  549    { pack_property(_,_),
  550      !,
  551      http_link_to_id(pldoc_pack, [], HREF),
  552      format(atom(Call), 'document.location=\'~w\';', [HREF])
  553    },
  554    html(option([ class(packs),
  555                  onClick(Call),
  556                  value(':packs:')
  557                ],
  558                'List extension packs')).
  559packs_link -->
  560    [].
 source_directory(+Dir) is semidet
source_directory(-Dir) is nondet
True if Dir is a directory from which we have loaded Prolog sources.
  568source_directory(Dir) :-
  569    (   ground(Dir)
  570    ->  '$time_source_file'(File, _Time1, _System1),
  571        file_directory_name(File, Dir), !
  572    ;   '$time_source_file'(File, _Time2, _System2),
  573        file_directory_name(File, Dir)
  574    )