View source with formatted comments or as raw
    1/*  Part of ClioPatria
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2010-2012 University of Amsterdam
    7                             CWI, Asterdam
    8                             VU University 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(cp_help, []).   38:- use_module(library(doc_http)).               % Load pldoc
   39:- use_module(library(pldoc/doc_index)).        % PlDoc Search menu
   40:- use_module(library(http/http_hook)).         % Get hook signatures
   41:- use_module(library(http/http_dispatch)).     % Get hook signatures
   42:- use_module(library(http/html_write)).   43:- use_module(library(http/html_head)).   44:- include(library(pldoc/hooks)).
   45
   46:- use_module(cliopatria(parms)).       % Get paths
   47:- use_module(skin(cliopatria)).        % Skinning primitives
   48:- use_module(wiki).                    % Our own help-pages
   49:- use_module(http_help).               % Help on HTTP server
   50:- use_module(ac_predicate).            % Predicate autocompletion
   51:- use_module(components(menu)).        % ClioPatria Menu
   52
   53/** <module> ClioPatria help system
   54
   55This   module   serves   the   wiki-source     based   help-pages   from
   56cliopatria(web/help)  and  integrates   SWI-Prolog's    PlDoc   literate
   57programming system to provide documentation of the source-code.
   58*/
   59
   60:- if(current_predicate(doc_enable/1)).   61:- initialization
   62    doc_enable(true).   63:- endif.   64
   65%       http:location(pldoc, Location, Options) is det.
   66%
   67%       Rebase PlDoc to <prefix>/help/source/
   68
   69http:location(pldoc, root('help/source'), [priority(10)]).
   70
   71:- http_handler(root(help/source), cp_help, []).   72:- http_handler(cliopatria('help/'),
   73                serve_page(help), [prefix, id(wiki_help)]).   74:- http_handler(cliopatria('tutorial/'),
   75                serve_page(tutorial), [prefix, id(tutorial)]).   76
   77%!  prolog:doc_directory(+Dir) is semidet.
   78%
   79%   True if we allow PlDoc to  serve   files  from  Dir. This allows
   80%   serving all files in the ClioPatria hierarchy.
   81
   82prolog:doc_directory(Dir) :-
   83    absolute_file_name(cliopatria(.), CpDir,
   84                       [ file_type(directory),
   85                         access(read)
   86                       ]),
   87    sub_atom(Dir, 0, _, _, CpDir).
   88
   89%!  cp_help(+Request)
   90%
   91%   HTTP handler that integrates a customised   version of PlDoc for
   92%   ClioPatria.  The opening page shows the file RoadMap.txt.
   93
   94cp_help(Request) :-
   95    http_location_by_id(pldoc_doc, Location),
   96    absolute_file_name(cliopatria('RoadMap'), HelpFile,
   97                       [ extensions([txt]),
   98                         access(read)
   99                       ]),
  100    atom_concat(Location, HelpFile, StartPage),
  101    http_redirect(moved, StartPage, Request).
  102
  103%!  cliopatria:menu_item(-Item, -Label) is nondet.
  104%
  105%   Extends the help popup with  links   to  the source-code and the
  106%   HTTP services.
  107
  108:- multifile
  109    cliopatria:menu_item/2.  110
  111cliopatria:menu_item(100=help/wiki_help, 'Documentation').
  112cliopatria:menu_item(150=help/tutorial,  'Tutorial').
  113cliopatria:menu_item(200=help/cp_help,   'Roadmap').
  114cliopatria:menu_item(300=help/http_help, 'HTTP Services').
  115
  116%!  user:body(+Style, :Body)// is det.
  117%
  118%   The multi-file implementation defines the overall layout of HTML
  119%   pages with the Style pldoc(_).
  120
  121:- multifile
  122    user:body//2.  123
  124user:body(pldoc(wiki), Content) -->
  125    { absolute_file_name(cliopatria(.), Dir,
  126                         [ file_type(directory),
  127                           access(read)
  128                         ])
  129    },
  130    html_requires(cliopatria),
  131    html(body(class('yui-skin-sam cliopatria'),
  132              [ div(class(menu), \cp_menu),
  133                br(clear(all)),
  134                div(class(content),
  135                    [ \doc_links(Dir, [])
  136                    | Content
  137                    ]),
  138                \server_address('ClioPatria')
  139              ])).
  140user:body(pldoc(_), Content) -->
  141    html_requires(cliopatria),
  142    html(body(class('yui-skin-sam cliopatria'),
  143              [ div(class(menu), \cp_menu),
  144                br(clear(all)),
  145                div(class(content), Content),
  146                \server_address('ClioPatria')
  147              ]))