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)  2012, VU University Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(pldoc_pack,
   36          [ doc_pack/1                  % +Pack
   37          ]).   38:- use_module(library(prolog_pack)).   39:- use_module(library(http/html_write)).   40:- use_module(library(http/html_head)).   41:- use_module(library(http/http_dispatch)).   42:- use_module(doc_html).   43:- use_module(doc_index).

PlDoc for Prolog extension packs

This module profiles PlDoc support specific to Prolog extension packs. It extends the PlDoc web-browser with the ability to lists the installed packs and provide an overview of a pack, whether loaded or not. The predicate doc_pack/1 can be used to generate stand-alone HTML documentation for a pack. */

   54:- http_handler(pldoc(pack),     http_redirect(moved, pldoc('pack/')), []).   55:- http_handler(pldoc('pack/'),  pldoc_pack, [prefix]).
 pldoc_pack(+Request)
HTTP handler that handles /pack/ in the PlDoc server. Without an additional path, it lists the installed packs. With an additional package name, it lists the content of a pack and finally, /pack/<pack>/<file> can be used to get documentation or the source of a pack file.
   65pldoc_pack(Request) :-
   66    memberchk(path_info(PackPath), Request),
   67    PackPath \== '',
   68    !,
   69    (   pack_path(Pack, PackFile, PackPath)
   70    ->  list_pack(Pack, PackFile, Request)
   71    ;   http_404([], Request)
   72    ).
   73pldoc_pack(_Request) :-
   74    reply_html_page(
   75        pldoc(packs),
   76        title('Installed extension packs'),
   77        \pack_page([])).
   78
   79pack_path(Pack, PackFile, PackPath) :-
   80    sub_atom(PackPath, B, _, A, /),
   81    !,
   82    sub_atom(PackPath, 0, B, _, Pack),
   83    sub_atom(PackPath, _, A, 0, PackFile).
   84
   85pack_page(Options) -->
   86    html_requires(pldoc),
   87    object_page_header(-, Options),
   88    html([ h1('Installed extension packs'),
   89           p([ 'The following extension packages are installed in ',
   90               'the this Prolog system.  Other packages can be found at ',
   91               a(href('http://www.swi-prolog.org/pack/list'),
   92                 'the SWI-Prolog website')
   93             ]),
   94           \pack_table(Options)
   95         ]).
 pack_table(+Options)// is det
Generate a table with installed packages
  102pack_table(_Options) -->
  103    { findall(Pack, pack_property(Pack, directory(_)), Packs0),
  104      sort(Packs0, Packs)
  105    },
  106    html(table(class(packs),
  107               [ tr([th('Pack'), th('Version'), th('Title')])
  108               | \packs(Packs)
  109               ])).
  110
  111packs([]) --> [].
  112packs([H|T]) --> pack(H), packs(T).
  113
  114pack(Pack) -->
  115    { uri_encoded(path, Pack, HREF),
  116      pack_property(Pack, version(Version)),
  117      (   pack_property(Pack, title(Title))
  118      ->  true
  119      ;   Title = '<no title>'
  120      )
  121    },
  122    html(tr([ td(class(pack_name),    a(href(HREF+'/'), Pack)),
  123              td(class(pack_version), Version),
  124              td(class(pack_title),   Title)
  125            ])).
 list_pack(+Pack, +PackFile, +Request)
List a directory or file in a pack
  132list_pack(Pack, '', _) :-
  133    !,
  134    reply_html_page(
  135        pldoc(pack),
  136        title('Documentation for pack ~w'-[Pack]),
  137        \pack_doc(Pack)).
  138list_pack(Pack, File, Request) :-
  139    pack_property(Pack, directory(PackDir)),
  140    directory_file_path(PackDir, File, Path0),
  141    absolute_file_name(Path0, Path),        % Canonical
  142    sub_atom(Path, 0, _, _, PackDir),
  143    pldoc_http:doc_reply_file(Path, Request).
  144
  145pack_doc(Pack) -->
  146    { pack_property(Pack, directory(PackDir)),
  147      pack_title(Pack, Title),
  148      findall(O, pack_option(Pack, O), Options)
  149    },
  150    dir_index(PackDir,
  151              [ if(true),
  152                recursive(true),
  153                title(Title)
  154              | Options
  155              ]).
  156
  157
  158                 /*******************************
  159                 *        STAND ALONE DOCS      *
  160                 *******************************/
 doc_pack(+Pack)
Generate stand-alone documentation for the package Pack. The documentation is generated in a directory doc inside the pack. The index page consists of the content of readme or readme.txt in the main directory of the pack and an index of all files and their public predicates.
  170doc_pack(Pack) :-
  171    pack_property(Pack, directory(PackDir)),
  172    pack_title(Pack, PackTitle),
  173    findall(O, pack_option(Pack, O), Options),
  174    directory_file_path(PackDir, prolog, SourceDir),
  175    directory_file_path(PackDir, doc, DocDir),
  176    doc_save(SourceDir,
  177             [ title(PackTitle),
  178               doc_root(DocDir),
  179               if(true),
  180               recursive(true)
  181             | Options
  182             ]).
  183
  184pack_title(Pack, PackTitle) :-
  185    pack_property(Pack, title(Title)),
  186    !,
  187    format(atom(PackTitle), 'Pack ~w -- ~w', [Pack, Title]).
  188pack_title(Pack, PackTitle) :-
  189    format(atom(PackTitle), 'Pack ~w', [Pack]).
  190
  191pack_option(Pack, Option) :-
  192    pack_option(Option),
  193    pack_property(Pack, Option).
  194
  195pack_option(readme(_)).
  196pack_option(todo(_))