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
   52:- if(exists_source(library(doc_http))).   53:- use_module(library(http/http_dispatch)).   54:- use_module(library(doc_http), []).   55:- endif.   56
   57:- use_module(library(http/html_write)).   58:- use_module(library(http/html_head)).   59:- use_module(library(readutil)).   60:- use_module(library(url)).   61:- use_module(library(option)).   62:- use_module(library(lists)).   63:- use_module(library(apply)).   64:- use_module(library(filesex)).   65:- use_module(library(prolog_pack)).   66:- use_module(library(prolog_source)).   67:- use_module(library(prolog_xref)).   68
   69:- include(hooks).

Create indexes

*/

   74:- predicate_options(dir_index//2, 2,
   75		     [ directory(atom),
   76		       edit(boolean),
   77		       files(list),
   78		       members(list),
   79		       qualify(boolean),
   80		       title(atom),
   81		       if(oneof([true,loaded])),
   82		       recursive(boolean),
   83		       secref_style(oneof([number, title, number_title])),
   84		       pass_to(doc_links/4, 2)
   85		     ]).   86:- predicate_options(doc_links//2, 2,
   87		     [ files(list),
   88		       pass_to(pldoc_search:search_form/3, 1)
   89		     ]).   90:- predicate_options(file_index_header//2, 2,
   91		     [ directory(any),
   92		       files(list),
   93		       qualify(boolean),
   94		       secref_style(oneof([number, title, number_title])),
   95		       pass_to(pldoc_html:edit_button/4, 2),
   96		       pass_to(pldoc_html:source_button/4, 2)
   97		     ]).   98:- predicate_options(object_summaries//3, 3,
   99		     [ edit(boolean),
  100		       files(list),
  101		       module(atom),
  102		       public(list),
  103		       qualify(boolean),
  104		       secref_style(oneof([number, title, number_title]))
  105		     ]).  106:- 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).
  115doc_for_dir(DirSpec, Options) :-
  116    absolute_file_name(DirSpec,
  117                       Dir,
  118		       [ file_type(directory),
  119			 access(read)
  120		       ]),
  121    (   option(title(Title), Options)
  122    ->  true
  123    ;   file_base_name(Dir, Title)
  124    ),
  125    doc_write_page(
  126	pldoc(dir_index),
  127	title(Title),
  128	\dir_index(Dir, Options),
  129	Options).
  130
  131:- html_meta doc_write_page(+, html, html, +).  132
  133doc_write_page(Style, Head, Body, Options) :-
  134    option(files(_), Options),
  135    !,
  136    phrase(page(Style, Head, Body), HTML),
  137    print_html(HTML).
  138doc_write_page(Style, Head, Body, _) :-
  139    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
  152dir_index(Dir, Options) -->
  153    { dir_source_files(Dir, Files0, Options),
  154      sort(Files0, Files),
  155      maplist(ensure_doc_objects, Files),
  156      directory_file_path(Dir, 'index.html', File),
  157      b_setval(pldoc_file, File)    % for predref
  158    },
  159    html([ \doc_resources(Options),
  160	   \doc_links(Dir, Options),
  161	   \dir_header(Dir, Options),
  162	   \subdir_links(Dir, Options),
  163	   h2(class([wiki,plfiles]), 'Prolog files'),
  164	   table(class(summary),
  165		 \file_indices(Files, [directory(Dir)|Options])),
  166	   \dir_footer(Dir, Options)
  167	 ]).
 dir_source_files(+Dir, -Files, +Options) is det
Create a list of source-files to be documented as part of Dir.
  173dir_source_files(_, Files, Options) :-
  174    option(members(Members), Options),
  175    !,
  176    findall(F, member(file(F,_Doc), Members), Files).
  177dir_source_files(Dir, Files, Options) :-
  178    directory_source_files(Dir, Files, Options).
 subdir_links(+Dir, +Options)// is det
Create links to subdirectories
  184subdir_links(Dir, Options) -->
  185    { option(members(Members), Options),
  186      findall(SubDir, member(directory(SubDir, _, _, _), Members), SubDirs),
  187      SubDirs \== []
  188    },
  189    html([ h2(class([wiki,subdirs]), 'Sub directories'),
  190	   table(class(subdirs),
  191		 \subdir_link_rows(SubDirs, Dir))
  192	 ]).
  193subdir_links(_, _) --> [].
  194
  195subdir_link_rows([], _) --> [].
  196subdir_link_rows([H|T], Dir) -->
  197    subdir_link_row(H, Dir),
  198    subdir_link_rows(T, Dir).
  199
  200subdir_link_row(Dir, From) -->
  201    { directory_file_path(Dir, 'index.html', Index),
  202      relative_file_name(Index, From, Link),
  203      file_base_name(Dir, Base)
  204    },
  205    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.
  214dir_header(Dir, Options) -->
  215    wiki_file(Dir, readme, Options),
  216    !.
  217dir_header(Dir, Options) -->
  218    { (   option(title(Title), Options)
  219      ->  true
  220      ;   file_base_name(Dir, Title)
  221      )
  222    },
  223    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.
  233dir_footer(Dir, Options) -->
  234    wiki_file(Dir, todo, Options),
  235    !.
  236dir_footer(_, _) -->
  237    [].
 wiki_file(+Dir, +Type, +Options)// is semidet
Include text from a Wiki text-file.
  243wiki_file(Dir, Type, Options) -->
  244    { (   Opt =.. [Type,WikiFile],
  245	  option(Opt, Options)
  246      ->  true
  247      ;   directory_files(Dir, Files),
  248	  member(File, Files),
  249	  wiki_file_type(Type, Pattern),
  250	  downcase_atom(File, Pattern),
  251	  directory_file_path(Dir, File, WikiFile)
  252      ),
  253      access_file(WikiFile, read),
  254      !,
  255      read_file_to_codes(WikiFile, String, []),
  256      wiki_codes_to_dom(String, [], DOM)
  257    },
  258    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.
  265wiki_file_type(readme, 'readme').
  266wiki_file_type(readme, 'readme.md').
  267wiki_file_type(readme, 'readme.txt').
  268wiki_file_type(todo,   'todo').
  269wiki_file_type(todo,   'todo.md').
  270wiki_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.
  277file_indices([], _) -->
  278    [].
  279file_indices([H|T], Options) -->
  280    file_index(H, Options),
  281    file_indices(T, Options).
 file_index(+File, +Options)// is det
Create an index for File.
  287file_index(File, Options) -->
  288    { doc_summaries(File, Objs0),
  289      module_info(File, ModuleOptions, Options),
  290      doc_hide_private(Objs0, Objs1, ModuleOptions),
  291      sort(Objs1, Objs)
  292    },
  293    html([ \file_index_header(File, Options)
  294	 | \object_summaries(Objs, File, ModuleOptions)
  295	 ]).
  296
  297doc_summaries(File, Objects) :-
  298    xref_current_source(FileSpec),
  299    xref_option(FileSpec, comments(collect)),
  300    !,
  301    Pos = File:0,
  302    findall(doc(Obj,Pos,Summary),
  303	    xref_doc_summary(Obj, Pos, Summary), Objects).
  304doc_summaries(File, Objects) :-
  305    Pos = File:_Line,
  306    findall(doc(Obj,Pos,Summary),
  307	    doc_comment(Obj, Pos, Summary, _), Objects).
  308
  309xref_doc_summary(M:Name/Arity, File:_, Summary) :-
  310    xref_comment(File, Head, Summary, _Comment),
  311    xref_module(File, Module),
  312    strip_module(Module:Head, M, Plain),
  313    functor(Plain, Name, Arity).
 file_index_header(+File, +Options)// is det
Create an entry in a summary-table for File.
  319file_index_header(File, Options) -->
  320    prolog:doc_file_index_header(File, Options),
  321    !.
  322file_index_header(File, Options) -->
  323    { (   option(directory(Dir), Options),
  324	  directory_file_path(Dir, Label, File)
  325      ->  true
  326      ;   file_base_name(File, Label)
  327      ),
  328      doc_file_href(File, HREF, Options)
  329    },
  330    html(tr(th([colspan(3), class(file)],
  331	       [ span(style('float:left'), a(href(HREF), Label)),
  332		 \file_module_title(File),
  333		 span(style('float:right'),
  334		      [ \source_button(File, Options),
  335			\edit_button(File, Options)
  336		      ])
  337	       ]))).
  338
  339file_module_title(File) -->
  340    { (   module_property(M, file(File))
  341      ;   xref_module(File, M)
  342      ),
  343      doc_comment(M:module(Title), _, _, _)
  344    },
  345    !,
  346    html([&(nbsp), ' -- ', Title]).
  347file_module_title(_) -->
  348    [].
 doc_file_href(+File, -HREF, +Options) is det
HREF is reference to documentation of File.
  355doc_file_href(File, HREF, Options) :-
  356    option(directory(Dir), Options),
  357    atom_concat(Dir, Local0, File),
  358    atom_concat(/, Local, Local0),
  359    !,
  360    (   option(files(Map), Options),        % generating files
  361	memberchk(file(File, DocFile), Map)
  362    ->  file_base_name(DocFile, HREF)
  363    ;   HREF = Local
  364    ).
  365doc_file_href(File, HREF, _) :-
  366    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.
  378doc_file_href(File0, HREF) :-
  379    insert_alias(File0, File),
  380    ensure_slash_start(File, SlashFile),
  381    http_location([path(SlashFile)], Escaped),
  382    http_location_by_id(pldoc_doc, DocRoot),
  383    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 ...
  391ensure_slash_start(File, File) :-
  392    sub_atom(File, 0, _, _, /),
  393    !.
  394ensure_slash_start(File0, File) :-
  395    atom_concat(/, File0, File).
 object_summaries(+Objects, +Section, +Options)// is det
Create entries in a summary table for Objects.
  402object_summaries(Objects, Section, Options) -->
  403    { tag_pub_priv(Objects, Tagged, Options),
  404      keysort(Tagged, Ordered)
  405    },
  406    obj_summaries(Ordered, Section, Options).
  407
  408obj_summaries([], _, _) -->
  409    [].
  410obj_summaries([_Tag-H|T], Section, Options) -->
  411    object_summary(H, Section, Options),
  412    obj_summaries(T, Section, Options).
  413
  414tag_pub_priv([], [], _).
  415tag_pub_priv([H|T0], [Tag-H|T], Options) :-
  416    (   private(H, Options)
  417    ->  Tag = z_private
  418    ;   Tag = a_public
  419    ),
  420    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?
  430object_summary(q(_Q,Obj), Section, Options) -->
  431    { nonvar(Obj) },
  432    !,
  433    object_summary(Obj, Section, Options).
  434object_summary(doc(Obj, _Pos, _Summary), wiki, Options) -->
  435    !,
  436    html(tr(class(wiki),
  437	    [ td(colspan(3), \object_ref(Obj, Options))
  438	    ])).
  439object_summary(doc(Obj, _Pos, Summary), _Section, Options) -->
  440    !,
  441    (   { string_codes(Summary, Codes),
  442	  wiki_codes_to_dom(Codes, [], DOM0),
  443	  strip_leading_par(DOM0, DOM),
  444	  (   private(Obj, Options)
  445	  ->  Class = private               % private definition
  446	  ;   Class = public                % public definition
  447	  )
  448	}
  449    ->  html(tr(class(Class),
  450		[ td(\object_ref(Obj, Options)),
  451		  td(class(summary), DOM),
  452		  td([align(right)],
  453		     span(style('white-space: nowrap'),
  454			  [ \object_source_button(Obj, Options),
  455			    \object_edit_button(Obj, Options)
  456			  ]))
  457		]))
  458    ;   []
  459    ).
  460object_summary(Obj, Section, Options) -->
  461    { prolog:doc_object_summary(Obj, _Cat, Section, Summary)
  462    },
  463    !,
  464    object_summary(doc(Obj, _, Summary), Section, Options).
  465object_summary(_, _, _) -->
  466    [].
  467
  468
  469		 /*******************************
  470		 *          NAVIGATION          *
  471		 *******************************/
 doc_links(+Directory, +Options)// is det
Provide overview links and search facilities.
  477doc_links(_Directory, Options) -->
  478    { option(files(_), Options), !
  479    }.
  480doc_links(Directory, Options) -->
  481    prolog:doc_links(Directory, Options),
  482    !,
  483    { option(html_resources(Resoures), Options, pldoc) },
  484    html_requires(Resoures).
  485doc_links(Directory, Options) -->
  486    {   (   Directory == ''
  487	->  working_directory(Dir, Dir)
  488	;   Dir = Directory
  489	),
  490	option(html_resources(Resoures), Options, pldoc)
  491    },
  492    html([ \html_requires(Resoures),
  493	   div(class(navhdr),
  494	       [ div(class(jump),
  495		      div([ \places_menu(Dir),
  496			    \plversion
  497			  ])),
  498		 div(class(search), \search_form(Options)),
  499		 br(clear(right))
  500	       ])
  501	 ]).
 version// is det
Prolog version
  508plversion -->
  509    { current_prolog_flag(version_data, swi(Major, Minor, Patch, _))
  510    },
  511    !,
  512    html(a([ class(prolog_version),
  513	     href('http://www.swi-prolog.org')
  514	   ],
  515	   [' SWI-Prolog ', Major, '.', Minor, '.', Patch])).
  516
  517plversion -->
  518    { current_prolog_flag(version_data, yap(Major, Minor, Patch, _))
  519    },
  520    html(a([ class(prolog_version),
  521	     href('http://www.dcc.fc.up.pt/~vsc')
  522	   ],
  523	   [' YAP ', Major, '.', Minor, '.', Patch])).
 places_menu(Current)// is det
Create a select menu with entries for all loaded directories
  530places_menu(Dir) -->
  531    prolog:doc_places_menu(Dir),
  532    !.
  533places_menu(Dir) -->
  534    { findall(D, source_directory(D), List),
  535      sort(List, Dirs)
  536    },
  537    html(form([ action(location_by_id(go_place))
  538	      ],
  539	      [ input([type(submit), value('Go')]),
  540		select(name(place),
  541		       \packs_source_dirs(Dirs, Dir))
  542	      ])).
  543
  544packs_source_dirs(Dirs, Dir) -->
  545    packs_link,
  546    source_dirs(Dirs, Dir).
  547
  548source_dirs([], _) -->
  549    [].
  550source_dirs([H|T], WD) -->
  551    { (   H == WD
  552      ->  Attrs = [selected]
  553      ;   Attrs = []
  554      ),
  555      format(string(IndexFile), '~w/index.html', [H]),
  556      doc_file_href(IndexFile, HREF),
  557      format(string(Call), 'document.location=\'~w\';', [HREF])
  558    },
  559    html(option([onClick(Call)|Attrs], H)),
  560    source_dirs(T, WD).
  561
  562packs_link -->
  563    { pack_property(_,_),
  564      !,
  565      http_link_to_id(pldoc_pack, [], HREF),
  566      format(atom(Call), 'document.location=\'~w\';', [HREF])
  567    },
  568    html(option([ class(packs),
  569		  onClick(Call),
  570		  value(':packs:')
  571		],
  572		'List extension packs')).
  573packs_link -->
  574    [].
 source_directory(+Dir) is semidet
source_directory(-Dir) is nondet
True if Dir is a directory from which we have loaded Prolog sources.
  582source_directory(Dir) :-
  583    (   ground(Dir)
  584    ->  '$time_source_file'(File, _Time1, _System1),
  585	file_directory_name(File, Dir), !
  586    ;   '$time_source_file'(File, _Time2, _System2),
  587	file_directory_name(File, Dir)
  588    )