View source with formatted comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        jan@swi-prolog.org
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2010-2024, University of Amsterdam,
    7                              VU University Amsterdam
    8                              SWI-Prolog Solutions b.v.
    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(cpa_user, []).   38
   39:- use_module(rdfql(serql_xml_result)).   40:- use_module(library(http/http_open)).   41:- use_module(library(http/http_path)).   42:- use_module(library(http/html_head)).   43:- use_module(library(http/html_write)).   44:- use_module(library(http/js_write)).   45:- use_module(library(http/http_dispatch)).   46:- use_module(library(http/http_host)).   47:- use_module(library(http/cp_jquery)).   48:- use_module(api(rdflib)).   49:- use_module(user(user_db)).   50:- use_module(library(debug)).   51:- use_module(components(server_statistics)).   52:- use_module(components(query)).   53:- use_module(components(basics)).   54:- use_module(library(semweb/rdf_db)).   55:- use_module(library(semweb/rdf_library)).   56:- use_module(library(occurs)).   57:- use_module(library(aggregate)).   58:- use_module(library(apply)).   59:- use_module(library(lists)).   60:- use_module(library(sgml)).   61:- use_module(library(http/http_json)).   62:- use_module(library(http/http_server)).   63:- use_module(library(http/http_stream)).   64
   65/** <Module> Basic user (developer) interaction
   66
   67This module contains the main front-end of ClioPatria. It notably
   68provides the HTTP-handlers for / and /home:
   69
   70    $ / :
   71    This handler, with id=root, redirects either to /home (id=home) or
   72    to id=create_admin. The latter is issued if there is no initialised
   73    user-db.
   74
   75    $ /home :
   76    Provides the default welcome page of ClioPatria.
   77
   78If one develops an application on top   of  ClioPatria, it is adviced to
   79redefine the handler for =home=, as in:
   80
   81    ==
   82    :- http_handler('/welcome', home, []).
   83
   84    home(Request) :-
   85        ...
   86    ==
   87
   88If the application wants to provide  a   link  to the generic ClioPatria
   89administrative interface, it can do so by   linking  to the id=admin, as
   90in:
   91
   92    ==
   93        ...,
   94        { http_link_to_id(admin, [], AdminRef) },
   95        html(a(href(AdminRef), admin)),
   96        ...
   97    ==
   98*/
   99
  100:- http_handler(root('.'),                           root,
  101                [ priority(-100) ]).  102:- http_handler(cliopatria(home),                    home,
  103                [ priority(-100) ]).  104:- http_handler(cliopatria(admin),                   home,
  105                [ id(admin) ]).  106:- http_handler(cliopatria('user/query'),            query_form,
  107                [id(sparql_query_form)]).  108:- http_handler(cliopatria('user/statistics'),       statistics,              []).  109:- http_handler(cliopatria('user/loadFile'),         load_file_form,          []).  110:- http_handler(cliopatria('user/loadURL'),          load_url_form,           []).  111:- http_handler(cliopatria('user/loadLibraryRDF'),   load_library_rdf_form,   []).  112:- http_handler(cliopatria('user/clearRepository'),  clear_repository_form,   []).  113:- http_handler(cliopatria('user/removeStatements'), remove_statements_form,  []).  114
  115
  116%!  root(+Request)
  117%
  118%   Default ClioPatria handler for /.  The default handler redirects
  119%   to id=home, unless the use-info is not initialised. in that case
  120%   it redirects to id=create_admin.
  121
  122root(Request) :-
  123    redirect_create_admin(Request),
  124    http_redirect(moved_temporary,
  125                  location_by_id(home),
  126                  Request).
  127
  128redirect_create_admin(Request) :-
  129    \+ current_user(_),
  130    !,
  131    http_redirect(moved_temporary,
  132                  location_by_id(create_admin),
  133                  Request).
  134redirect_create_admin(_).
  135
  136%!  home(+Request)
  137%
  138%   Reply with the normal  welcome  page.   The  welcome  page  is a
  139%   decorated version of html('welcome.html').
  140
  141home(Request) :-
  142    redirect_create_admin(Request),
  143    reply_decorated_file(html('welcome.html'), Request).
  144
  145
  146%!  reply_decorated_file(+Alias, +Request) is det.
  147%
  148%   Present an HTML file embedded using  the server styling. This is
  149%   achieved by parsing the  HTML  and   passing  the  parsed DOM to
  150%   reply_html_page/3.
  151
  152reply_decorated_file(Alias, _Request) :-
  153    absolute_file_name(Alias, Page, [access(read)]),
  154    load_html_file(Page, DOM),
  155    contains_term(element(title, _, Title), DOM),
  156    contains_term(element(body, _, Body), DOM),
  157    Style = element(style, _, _),
  158    findall(Style, sub_term(Style, DOM), Styles),
  159    append(Styles, Body, Content),
  160    reply_html_page(cliopatria(html_file),
  161                    title(Title), Content).
  162
  163
  164                 /*******************************
  165                 *          STATISTICS          *
  166                 *******************************/
  167
  168%!  statistics(+Request)
  169%
  170%   Provide elementary statistics on the server.
  171
  172statistics(Request) :-
  173    http_current_host(Request, Host, _Port, [global(true)]),
  174    reply_html_page(cliopatria(default),
  175                    title('RDF statistics'),
  176                    [ div(id('rdf-statistics'),
  177                          [ h1([id(stattitle)], ['RDF statistics for ', Host]),
  178                            ol([id(toc)],
  179                               [ li(a(href('#ntriples'),    'Triples in database')),
  180                                 li(a(href('#callstats'),   'Call statistics')),
  181                                 li(a(href('#sessions'),    'Active sessions')),
  182                                 li(a(href('#serverstats'), 'Server statistics'))
  183                               ]),
  184                            h2([id(ntriples)], 'Triples in database'),
  185                            \triple_statistics,
  186                            h2([id(callstats)],'Call statistics'),
  187                            \rdf_call_statistics_table,
  188                            h2([id(sessions)], 'Active sessions'),
  189                            \http_session_table,
  190                            h2([id(serverstats)], 'Server statistics'),
  191                            h3('Static workers and statistics:'),
  192                            \http_server_statistics,
  193                            h3('Defined dynamic worker pools:'),
  194                            \http_server_pool_table
  195                          ])
  196                    ]).
  197
  198
  199triple_statistics -->
  200    { rdf_statistics(triples(Total)),
  201      graph_count(Count),
  202      http_link_to_id(list_graphs, [], ListGraphs)
  203    },
  204    html(p([ 'The RDF store contains ', \n(human, Total), ' triples in ',
  205             \n(human, Count), ' ', a(href(ListGraphs), graphs),
  206             \using_core])).
  207
  208:- if((rdf_version(V),V<30000)).  209using_core -->
  210    { rdf_statistics(core(Core)) },
  211    !,
  212    html([', using ', \n(human, Core), 'b memory']).
  213:- endif.  214using_core -->
  215    [].
  216
  217graph_count(Count) :-
  218    aggregate_all(count, rdf_graph(_), Count).
  219
  220:- if(exists_source(library(http/http_server_health))).  221:- use_module(library(http/http_server_health)).  222:- http_handler(cliopatria(health), server_health, []).  223:- else.  224:- http_handler(cliopatria('health'), health, []).  225
  226%!  health(+Request)
  227%
  228%   Provide basic statistics for health checks
  229
  230%%	health(+Request)
  231%
  232%	HTTP handler that replies with the overall health of the server
  233
  234health(_Request) :-
  235	get_server_health(Health),
  236	reply_json(Health).
  237
  238get_server_health(Health) :-
  239	findall(Key-Value, health(Key, Value), Pairs),
  240	dict_pairs(Health, health, Pairs).
  241
  242health(up, true).
  243health(uptime, Time) :-
  244	get_time(Now),
  245	(   http_server_property(_, start_time(StartTime))
  246	->  Time is round(Now - StartTime)
  247	).
  248health(requests, RequestCount) :-
  249	cgi_statistics(requests(RequestCount)).
  250health(bytes_sent, BytesSent) :-
  251	cgi_statistics(bytes_sent(BytesSent)).
  252health(open_files, Streams) :-
  253	aggregate_all(count, N, stream_property(_, file_no(N)), Streams).
  254health(loadavg, LoadAVG) :-
  255	catch(setup_call_cleanup(
  256		  open('/proc/loadavg', read, In),
  257		  read_string(In, _, String),
  258		  close(In)),
  259	      _, fail),
  260	split_string(String, " ", " ", [One,Five,Fifteen|_]),
  261	maplist(number_string, LoadAVG, [One,Five,Fifteen]).
  262:- if(current_predicate(malloc_property/1)).  263health(heap, json{inuse:InUse, size:Size}) :-
  264	malloc_property('generic.current_allocated_bytes'(InUse)),
  265	malloc_property('generic.heap_size'(Size)).
  266:- endif.  267:- endif. % have library(http/http_server_health).
  268
  269
  270%!  query_form(+Request)
  271%
  272%   Provide a page for issuing a =SELECT= query.
  273
  274query_form(_Request) :-
  275    reply_html_page(cliopatria(default),
  276                    title('Specify a query'),
  277                    [ \query_form([]),
  278                      \query_docs,
  279                      \warn_interactive
  280                    ]).
  281
  282
  283
  284warn_interactive -->
  285    { http_location_by_id(sparql_query, HREF),
  286      SparqlAPI = 'http://www.w3.org/TR/rdf-sparql-protocol/'
  287    },
  288    html([ br(clear(all)),
  289           p(class(footnote),
  290             [ 'This form is to test SPARQL queries ', i(interactively), '. ',
  291               'Machines should use ', b([HREF,'?query=...']),
  292               ', which provides a ',
  293               a(href(SparqlAPI), 'SPARQL compliant HTTP API'), '.'
  294             ])
  295         ]).
  296
  297query_docs -->
  298    html(ul([ li(a(href('http://www.w3.org/TR/rdf-sparql-query/'),
  299                   'SPARQL Documentation')),
  300              li(a(href('http://rdf4j.org/'),
  301                   'Sesame and SeRQL site'))
  302            ])).
  303
  304%!  load_file_form(+Request)
  305%
  306%   Provide a form for uploading triples from a local file.
  307
  308load_file_form(Request) :-
  309    authorized(write(default, load(posted))),
  310    reply_html_page(cliopatria(default),
  311                    title('Upload RDF'),
  312                    [ h1('Upload an RDF document'),
  313
  314                      \explain_file_form,
  315
  316                      form([ action(location_by_id(upload_data)),
  317                             method('POST'),
  318                             enctype('multipart/form-data')
  319                           ],
  320                           [ \hidden(resultFormat, html),
  321                             table(class(form),
  322                                   [tr([ th(class(label), 'File:'),
  323                                         td(input([ name(data),
  324                                                    id(filename),
  325                                                    type(file),
  326                                                    size(50)
  327                                                  ]))
  328                                       ]),
  329                                    tr([ th(class(label), 'Graph:'),
  330                                         td(input([ name(baseURI),
  331                                                    id(namedgraph),
  332                                                    size(50)
  333                                                  ]))
  334                                       ]),
  335                                    tr(class(buttons),
  336                                       [ th([align(right), colspan(2)],
  337                                            input([ type(submit),
  338                                                    value('Upload now')
  339                                                  ]))
  340                                       ])
  341                                   ])
  342                           ]),
  343                      \graph_script(Request)
  344                    ]).
  345
  346explain_file_form -->
  347    html({|html||
  348<p>Upload RDF to the ClioPatria triple store. The uploaded file may
  349contain <a href="http://www.w3.org/TR/REC-rdf-syntax/">RDF/XML</a>, <a
  350href="http://www.w3.org/TR/turtle/">Turtle</a> or <a
  351href="http://www.w3.org/TR/n-triples/">ntriples</a>. The file is
  352processed using <a href="http://www.libarchive.org/"> libarchive</a>,
  353which implies it can be a (nested) archive and may optionally be
  354compressed. </p>
  355
  356<p>
  357Alternatively you can use <a href="loadURL">loadURL</a> to load data from a web server.
  358</p>
  359         |}).
  360
  361
  362graph_script(Request) -->
  363    { http_public_host_url(Request, Host),
  364      http_absolute_location(root(data/uploaded), Location, []),
  365      string_concat(Host, Location, URL)
  366    },
  367    html_requires(jquery),
  368    js_script({|javascript(URL)||
  369$(function() {
  370  if ( $("#filename").val() ) {
  371    $("#namedgraph").val(URL+"/"+$("#filename").val());
  372  }
  373
  374  $("#filename").on("change", function(ev) {
  375    var filename = $(ev.target).val();
  376    console.log("Changed file", filename);
  377    $("#namedgraph").val(URL+"/"+filename);
  378  });
  379});
  380              |}).
  381
  382
  383%!  load_url_form(+Request)
  384%
  385%   Provide a form for uploading triples from a URL.
  386
  387load_url_form(_Request) :-
  388    reply_html_page(cliopatria(default),
  389                    title('Load RDF from HTTP server'),
  390                    [ h1('Load RDF from HTTP server'),
  391
  392                      \explain_url_form,
  393
  394                      form([ action(location_by_id(upload_url)),
  395                             method('GET')
  396                           ],
  397                           [ \hidden(resultFormat, html),
  398                             table(class(form),
  399                                   [tr([ th(class(label), 'URL:'),
  400                                         td(input([ name(url),
  401                                                    id(url),
  402                                                    value('http://'),
  403                                                    size(50)
  404                                                  ]))
  405                                       ]),
  406                                    tr([ th(class(label), 'Graph:'),
  407                                         td(input([ name(baseURI),
  408                                                    id(namedgraph),
  409                                                    value('http://'),
  410                                                    size(50)
  411                                                  ]))
  412                                       ]),
  413                                    tr(class(buttons),
  414                                       [ td([align(right), colspan(2)],
  415                                            input([ type(submit),
  416                                                    value('Load RDF')
  417                                                  ]))
  418                                       ])
  419                                   ])
  420                           ]),
  421                      \url_graph_script
  422                    ]).
  423
  424
  425url_graph_script -->
  426    html_requires(jquery),
  427    js_script({|javascript||
  428$(function() {
  429  $("#url").on("change keyup", function(ev) {
  430    var url = $(ev.target).val();
  431    $("#namedgraph").val(url);
  432  });
  433});
  434              |}).
  435
  436
  437explain_url_form -->
  438    html({|html||
  439
  440<p>Download RDF from an URL and insert it into the ClioPatria triple
  441store. The downloaded document may contain <a
  442href="http://www.w3.org/TR/REC-rdf-syntax/">RDF/XML</a>, <a
  443href="http://www.w3.org/TR/turtle/">Turtle</a> or <a
  444href="http://www.w3.org/TR/n-triples/">ntriples</a>. The file is
  445processed using <a href="http://www.libarchive.org/"> libarchive</a>,
  446which implies it can be a (nested) archive and may optionally be
  447compressed. </p>
  448
  449<p>
  450Alternatively you can use <a href="loadFile">loadFile</a> to upload
  451a file through your browser.
  452</p>
  453         |}).
  454
  455%!  load_library_rdf_form(+Request)
  456%
  457%   Provide a form  for  loading  an   ontology  from  the  library.
  458%   Libraries are made  available  through   the  file  search  path
  459%   =ontology=. Directories found through this   alias  are searched
  460%   recursively for files named =|Manifest.ttl|=.
  461%
  462%   @see file_search_path/2
  463%   @see rdf_attach_library/1.
  464
  465load_library_rdf_form(Request) :-
  466    authorized(read(status, listBaseOntologies)),
  467    get_base_ontologies(Request, Ontologies),
  468    reply_html_page(cliopatria(default),
  469                    title('Load server-side RDF library'),
  470                    [ h1('Load a registered RDF library'),
  471                      p('Select a resource from the registered libraries'),
  472                      \load_base_ontology_form(Ontologies)
  473                    ]).
  474
  475
  476%!  load_base_ontology_form(+Ontologies)//
  477%
  478%   HTML component that emits a form to load a base-ontology and its
  479%   dependencies. Ontologies is a list   of  ontology-identifiers as
  480%   used by rdf_load_library/1.
  481
  482load_base_ontology_form(Ontologies) -->
  483    html(form([ action(location_by_id(load_library_ontology)),
  484                method('GET')
  485              ],
  486              [ \hidden(resultFormat, html),
  487                table(class(form),
  488                      [ tr([ th('Ontology:'),
  489                             td(select(name(ontology),
  490                                       [ option([], '')
  491                                       | \emit_base_ontologies(Ontologies)
  492                                       ]))
  493                           ]),
  494                        tr(class(buttons),
  495                           td([colspan(2), align(right)],
  496                              input([ type(submit),
  497                                      value('Load')
  498                                    ])))
  499                      ])
  500              ])).
  501
  502
  503emit_base_ontologies([]) -->
  504    [].
  505emit_base_ontologies([H|T]) -->
  506    (   { rdf_library_index(H, title(Title)) }
  507    ->  html(option([value(H)], [H, ' -- ', Title]))
  508    ;   html(option([value(H)], H))
  509    ),
  510    emit_base_ontologies(T).
  511
  512
  513get_base_ontologies(_Request, List) :-
  514    catch(findall(O, library_ontology(O), List0), _, fail),
  515    !,
  516    sort(List0, List).
  517get_base_ontologies(Request, List) :-
  518    http_current_host(Request, Host, Port, []),
  519    http_location_by_id(list_base_ontologies, ListBaseOntos),
  520    debug(base_ontologies, 'Opening http://~w:~w~w',
  521          [Host, Port, ListBaseOntos]),
  522    http_open([ protocol(http),
  523                host(Host),
  524                port(Port),
  525                path(ListBaseOntos),
  526                search([resultFormat(xml)])
  527              ],
  528              In,
  529              [ % request_header('Cookie', Cookie)
  530              ]),
  531    debug(base_ontologies, '--> Reading from ~w', [In]),
  532    xml_read_result_table(In, Rows, _VarNames),
  533    maplist(arg(1), Rows, List).
  534
  535%!  clear_repository_form(+Request)
  536%
  537%   HTTP handle presenting a form to clear the repository.
  538
  539clear_repository_form(_Request) :-
  540    reply_html_page(cliopatria(default),
  541                    title('Clear triple store'),
  542                    [ h1('Clear entire repository'),
  543
  544                      p(['This operation removes ', b(all), ' triples from \c
  545                          the RDF store.']),
  546
  547                      form([ action(location_by_id(clear_repository)),
  548                             method('GET')
  549                           ],
  550                           [ \hidden(repository, default),
  551                             \hidden(resultFormat, html),
  552                             input([ type(submit),
  553                                     value('Clear repository now')
  554                                   ])
  555                           ])
  556                    ]).
  557
  558
  559%!  remove_statements_form(+Request)
  560%
  561%   HTTP handler providing a form to remove RDF statements.
  562
  563remove_statements_form(_Request) :-
  564    reply_html_page(cliopatria(default),
  565                    title('Remove triples from store'),
  566                    [ h1('Remove statements'),
  567
  568                      p(['Remove matching triples from the database.  The three ',
  569                         'fields are in ntriples/Turtle notation.  Omitted fields ',
  570                         'match any value.'
  571                        ]),
  572
  573                      \remove_statements_form
  574                    ]).
  575
  576remove_statements_form -->
  577    html(form([ action(location_by_id(remove_statements)),
  578                method('GET')
  579              ],
  580              [ \hidden(repository, default),
  581                \hidden(resultFormat, html),
  582                table([ class(form)
  583                      ],
  584                      [ tr([ th(class(label), 'Subject:'),
  585                             td(input([ name(subject),
  586                                        size(50)
  587                                      ]))
  588                           ]),
  589                        tr([ th(class(label), 'Predicate:'),
  590                             td(input([ name(predicate),
  591                                        size(50)
  592                                      ]))
  593                           ]),
  594                        tr([ th(class(label), 'Object:'),
  595                             td(input([ name(object),
  596                                        size(50)
  597                                      ]))
  598                           ]),
  599                        tr(class(buttons),
  600                           [ td([ align(right),
  601                                  colspan(2)
  602                                ],
  603                                input([ type(submit),
  604                                        value('Remove')
  605                                      ]))
  606                           ])
  607                      ])
  608              ]))