View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2014-2015, VU University Amsterdam
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- module(swish_app,
   31	  [
   32	  ]).   33:- use_module(library(pengines)).   34:- use_module(library(option)).   35:- use_module(library(http/http_dispatch)).   36:- use_module(library(http/http_server_files)).   37:- use_module(library(http/http_json)).   38:- use_module(rdfql(sparql_csv_result)).   39
   40		 /*******************************
   41		 *	       PATHS		*
   42		 *******************************/
   43
   44:- multifile
   45        http:location/3,
   46        user:file_search_path/2.   47
   48http:location(swish, root(swish), []).
   49
   50user:file_search_path(render,     library(swish/render)).
   51user:file_search_path(swish_pack, library(swish/pack)).
   52
   53
   54		 /*******************************
   55		 *            MODULES		*
   56		 *******************************/
   57
   58:- use_module(library(swish/messages)).   59:- use_module(library(swish/paths)).   60:- use_module(library(swish/config)).   61:- use_module(library(swish/page), []).   62:- use_module(library(swish/storage)).   63:- use_module(library(swish/include)).   64:- use_module(library(swish/swish_csv)).   65:- use_module(library(swish/examples)).   66:- use_module(library(swish/profiles)).   67:- use_module(library(swish/help)).   68:- use_module(library(swish/highlight)).   69:- use_module(library(swish/markdown)).   70:- use_module(library(swish/render)).   71:- use_module(library(swish/template_hint)).   72:- use_module(library(swish/chat), []).   73
   74
   75		 /*******************************
   76		 *	      CONFIG		*
   77		 *******************************/
   78
   79:- multifile
   80	swish_config:config/2,
   81	swish_config:source_alias/2.   82
   83%%	swish_config:config(?Config, ?Value) is nondet.
   84%
   85%	All solutions of this predicate are  available in the JavaScript
   86%	object config.swish.config. Config must be an  atom that is also
   87%	a valid JavaScript identifier. Value  must   be  a value that is
   88%	valid for json_write_dict/2.  Defined config parameters:
   89%
   90%	  - show_beware
   91%	  If `true`, show the *Beware* modal dialog on startup
   92%	  - tabled_results
   93%	  If `true`, check the _table results_ checkbox by default.
   94%	  - application
   95%	  Name of the Pengine application.
   96%	  - csv_formats
   97%	  CSV output formats offered. For example, ClioPatria
   98%	  defines this as [rdf,prolog]. The first element is default.
   99%	  - community_examples
  100%	  Allow marking saved programs as example.  If marked, the
  101%	  programs are added to the Examples menu.
  102%	  - public_access
  103%	  If lib/authenticate.pl is loaded and this flag is `true`,
  104%	  _all_ access to SWISH demands authentication.  If false,
  105%	  only running queries and saving files is restricted. Note
  106%	  that this flag has no effect if no authentication module is
  107%	  loaded.
  108%	  - include_alias
  109%	  Alias for searching files for `:- include(Alias(Name)).`
  110%	  - ping
  111%	  Ping pengine status every N seconds.  Updates sparkline
  112%	  chart with stack usage.
  113%	  - notebook
  114%	  Dict holding options for notebooks:
  115%	    - eval_script
  116%	    Whether or not to evaluate JavaScript in cells
  117%	    - fullscreen
  118%	    Whether or not to start in fullscreen mode by default
  119%	  - fullscreen
  120%	  Dict holding options for fullscreen mode:
  121%	    - hide_navbar: hide the navigation bar when in fullscreen
  122%	      mode.
  123%	  - chat
  124%	  Activate the chat interface
  125%	  - default_query
  126%	  Initial query for the source search in an empty tab
  127%
  128%	These config options are commonly  overruled   using  one of the
  129%	configuration files. See `config-available` and `config-enabled`
  130%	directories.
  131%
  132%	The  defaults  below   are   for    small   installations.   See
  133%	`config-available/dim_large.pl` for a default   config for large
  134%	communities.
  135
  136% Allow other code to overrule the defaults from this file.
  137term_expansion(swish_config:config(Config, _Value), []) :-
  138	clause(swish_config:config(Config, _), _).
  139
  140swish_config:config(show_beware,        false).
  141swish_config:config(tabled_results,     true).
  142swish_config:config(application,        swish).
  143swish_config:config(csv_formats,        [rdf, prolog]).
  144swish_config:config(community_examples, true).
  145swish_config:config(public_access,      true).
  146swish_config:config(include_alias,	example).
  147swish_config:config(ping,		5).
  148swish_config:config(notebook,		_{ eval_script: true,
  149					   fullscreen: false
  150					 }).
  151swish_config:config(fullscreen,		_{ hide_navbar: true
  152					 }).
  153swish_config:config(chat,		true).
  154swish_config:config(default_query,	'').
  155
  156%%     swish_config:source_alias(Alias, Options) is nondet.
  157%
  158%      Specify access for files below a given _alias_. Options define
  159%
  160%        - access(Access)
  161%        One of `read` or `both`.  Default is `read`.
  162%        - if(Condition)
  163%        Provide additional conditions.  Defined conditions are:
  164%          - loaded
  165%          Only provide access to the file if it is loaded.
  166
  167
  168		 /*******************************
  169		 *	        CSV		*
  170		 *******************************/
  171
  172:- multifile
  173	swish_csv:write_answers/2,
  174	swish_csv:write_answers/3.  175
  176swish_csv:write_answers(Answers, VarTerm) :-
  177        Answers = [H|_],
  178        functor(H, rdf, _), !,
  179        sparql_write_csv_result(
  180            current_output,
  181            select(VarTerm, Answers),
  182            []).
  183
  184swish_csv:write_answers(Answers, VarTerm, Options) :-
  185        Answers = [H|_],
  186        functor(H, rdf, _),
  187	option(page(1), Options), !,
  188        sparql_write_csv_result(
  189            current_output,
  190            select(VarTerm, Answers),
  191            [ bnode_state(_-BNodes)
  192	    ]),
  193	nb_setval(rdf_csv_bnodes, BNodes).
  194swish_csv:write_answers(Answers, VarTerm, Options) :-
  195        Answers = [H|_],
  196        functor(H, rdf, _),
  197	option(page(Page), Options),
  198	Page > 1, !,
  199	nb_getval(rdf_csv_bnodes, BNodes0),
  200        sparql_write_csv_result(
  201            current_output,
  202            select(VarTerm, Answers),
  203            [ http_header(false),
  204	      header_row(false),
  205	      bnode_state(BNodes0-BNodes)
  206	    ]),
  207	nb_setval(rdf_csv_bnodes, BNodes).
  208swish_csv:write_answers(Answers, VarTerm, _Options) :-
  209	swish_csv:write_answers(Answers, VarTerm).
  210
  211
  212                 /*******************************
  213                 *   CREATE SWISH APPLICATION   *
  214                 *******************************/
  215
  216:- multifile
  217	pengines:prepare_module/3.  218
  219:- pengine_application(swish).  220:- use_rendering(swish:rdf).  221:- use_module(swish:library(swish/render)).  222:- use_module(swish:library(swish/trace)).  223:- use_module(swish:library(swish/projection)).  224:- use_module(swish:library(swish/jquery)).  225:- use_module(swish:library(swish/dashboard)).  226:- use_module(swish:library(pengines_io)).  227:- use_module(swish:library(semweb/rdf_db)).  228:- use_module(swish:library(semweb/rdfs)).  229:- use_module(swish:library(semweb/rdf_optimise)).  230:- use_module(swish:library(semweb/rdf_litindex)).  231:- use_module(swish:library(solution_sequences)).  232:- use_module(swish:library(aggregate)).  233pengines:prepare_module(Module, swish, _Options) :-
  234	pengines_io:pengine_bind_io_to_html(Module).
  235
  236% Libraries that are nice to have in SWISH, but cannot be loaded
  237% because they use directives that are considered unsafe.  We load
  238% them here, so they only need to be imported, which is just fine.
  239
  240:- use_module(library(clpfd), []).  241:- use_module(library(clpb), []).  242:- if(exists_source(library(semweb/rdf11))).  243:- use_module(library(semweb/rdf11), []).  244:- endif.  245
  246% rendering libraries
  247
  248:- use_module(library(swish/render/table),    []).  249:- use_module(library(swish/render/rdf),      []).  250:- use_module(library(swish/render/graphviz), []).  251:- use_module(library(swish/render/c3),	      []).  252:- use_module(library(swish/render/swish),    []).