View source with raw comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2010-2018, 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(api_sparql,
   37          [
   38          ]).   39:- use_module(user(user_db)).   40:- use_module(library(lists)).   41:- use_module(library(option)).   42:- use_module(library(uri)).   43:- use_module(library(rdf_write)).   44:- use_module(library(http/http_parameters)).   45:- use_module(library(http/http_client)).   46:- use_module(library(http/http_dispatch)).   47:- use_module(library(http/http_request_value)).   48:- use_module(library(http/http_cors)).   49:- use_module(library(http/html_write)).   50:- use_module(rdfql(sparql)).   51:- use_module(rdfql(sparql_xml_result)).   52:- use_module(rdfql(sparql_json_result)).   53:- use_module(rdfql(sparql_csv_result)).   54:- use_module(library(settings)).   55:- if(exists_source(applications(yasgui))).   56:- use_module(applications(yasgui)).   57:- endif.   58
   59% We serve both `/sparql/`  and  `/sparql`.   The  first  is  merely for
   60% historical reasons. Note that we cannot turn  a path alias into a path
   61% without a `/`, so we must use root(sparql) as a hack.
   62
   63:- http_handler(sparql(.),      sparql_query,  [spawn(sparql_query), id('sparql_query/')]).   64:- http_handler(root(sparql),   sparql_query,  [spawn(sparql_query), id(sparql_query)]).   65:- http_handler(sparql(update), sparql_update, [spawn(sparql_query), id(sparql_update)]).
 sparql_query(+Request)
HTTP handler for SPARQL requests. Mounted the http-path sparql(.) (by default /sparql/, see library(http/http_path)).

As part of a SPARQL request the user may specify the following things:

  1. query The contents of the SPARQL query. Exactly one must occur in every SPARQL query request.
  2. default-graph The default graph as specified by the SPARQL dataset structure, against which the query is evaluated. Zero or more default graphs may be specified.
  3. `named-graph' The named graphs as specified by the SPARQL dataset structure, against which the query is evaluated. Zero or more named graphs may be specified.

    There are three ways of posing a SPARQL query:

  4. An HTTP GET request where query, default-graph and named-graph appear in the IRI's search string and are all subject to IRI-encoding. Example: `curl http://localhost:3020/sparql/?query=select%20*%20where%20%7B%20%3Fs%20%3Fp%20%3Fo%20%7D` No Content-Type needs to be specified.
  5. An HTTP POST request where query, default-graph and named-graph appear in the POST body using IRI search string syntax and subject to IRI-encoding. Example: `curl --data "query=select * where { ?s ?p ?o }" http://localhost:3020/sparql/` The Content-Type must be application/x-www-form-urlencoded.
  6. An HTTP POST request where default-graph and named-graph appear in the IRI's search string and are subject to IRI-encoding and where the query appears as-is in the POST body. Example: `curl -X POST -H "Content-Type: application/sparql-query" -d @query.sparql http://localhost:3020/sparql/` The Content-Type must be application/sparql-query.
  103sparql_query(Request) :-
  104    empty_get_request(Request),
  105    !,
  106    redirect_human_form(Request).
  107% Perform a SPARQL query via GET.
  108% @compat SPARQL 1.1 Protocol recommendation, section 2.1.1.
  109sparql_query(Request) :-
  110    memberchk(method(get), Request),
  111    !,
  112    sparql_query_parameters(Request).
  113% Perform a SPARQL query via POST with encoded parameters in body.
  114% @compat SPARQL 1.1 Protocol recommendation, section 2.1.2.
  115sparql_query(Request) :-
  116    memberchk(method(post), Request),
  117    memberchk(content_type(ContentType), Request),
  118    sub_atom(ContentType, 0, _, _, 'application/x-www-form-urlencoded'),
  119    !,
  120    catch(sparql_query_parameters(Request), E, sparql_query_exception(E)).
  121% Perform a SPARQL query via POST with unencoded body.
  122% @compat SPARQL 1.1 Protocol recommendation, section 2.1.3.
  123sparql_query(Request) :-
  124    memberchk(method(post), Request),
  125    memberchk(content_type(ContentType), Request),
  126    sub_atom(ContentType, 0, _, _, 'application/sparql-query'),
  127    !,
  128    http_parameters(Request,
  129                    [ 'default-graph-uri'(DefaultGraphs),
  130                      'named-graph-uri'(NamedGraphs),
  131                      format(ReqFormat),
  132                      entailment(Entailment)
  133                    ],
  134                    [ attribute_declarations(sparql_decl)
  135                    ]),
  136    append(DefaultGraphs, NamedGraphs, Graphs),
  137    http_read_data(Request, Query, []),
  138    authorized(read(Graphs, sparql)),
  139    sparql_reply(Request, Query, Graphs, ReqFormat, Entailment).
  140sparql_query(_) :-
  141    throw(http_reply(bad_request(format('Unrecognized SPARQL query request.', [])))).
  142
  143sparql_query_parameters(Request) :-
  144    http_parameters(Request,
  145                    [ query(Query),
  146                      'default-graph-uri'(DefaultGraphs),
  147                      'named-graph-uri'(NamedGraphs),
  148                      format(ReqFormat),
  149                      entailment(Entailment)
  150                    ],
  151                    [ attribute_declarations(sparql_decl)
  152                    ]),
  153    append(DefaultGraphs, NamedGraphs, Graphs),
  154    authorized(read(Graphs, sparql)),
  155    sparql_reply(Request, Query, Graphs, ReqFormat, Entailment).
  156
  157sparql_query_exception(E) :-
  158    E = error(syntax_error(illegal_uri_query),_),
  159    !,
  160    throw(http_reply(bad_request(format('Malformed search parameters.', [])))).
  161sparql_query_exception(E) :-
  162    throw(E).
 empty_get_request(+Request) is semidet
True if Request is an HTTP GET request without any parameters.
  168empty_get_request(Request) :-
  169    option(request_uri(URI), Request),
  170    uri_components(URI, Components),
  171    uri_data(search, Components, Search),
  172    var(Search),
  173    option(method(get), Request).
  174
  175:- if(current_predicate(has_yasgui/0)).  176human_form_location(HREF) :-
  177    has_yasgui,
  178    !,
  179    http_link_to_id(yasgui, [], HREF).
  180:- endif.  181human_form_location(HREF) :-
  182    http_link_to_id(sparql_query_form, [], HREF).
  183
  184redirect_human_form(Request) :-
  185    human_form_location(HREF),
  186    reply_html_page(cliopatria(default),
  187                    [ title('Redirect to SPARQL editor'),
  188                      meta([ 'http-equiv'(refresh),
  189                             content('5; url='+HREF)
  190                           ])
  191                    ], \sparql_redirect_explanation(Request, HREF)).
  192
  193sparql_redirect_explanation(Request, EditorHREF) -->
  194    { option(request_uri(URI), Request) },
  195    html({|html(URI, EditorHREF)||
  196<h4>Redirecting to SPARQL editor ...</h4>
  197
  198<div class="warning" style="width:80%;margin:auto;border:1px solid #888;padding: 10px 5px">
  199You have landed in the SPARQL access location <a href=URI>URI</a> of this server.
  200<b>This URI is intended for machines</b>.  Because your request contains no parameters,
  201you will be redirected to the SPARQL editor at <a href=EditorHREF>EditorHREF</a>
  202in 5 seconds.
  203</div>
  204             |}).
 sparql_update(+Request)
HTTP handler for SPARQL update requests. This is the same as query requests, but the takes the query in the update field rather than in the query field.
  214% Browser pointed here
  215sparql_update(Request) :-
  216    empty_get_request(Request),
  217    !,
  218    redirect_human_form(Request).
  219% Perform a SPARQL update via POST directly.
  220% @compat SPARQL 1.1 Protocol recommendation, section 2.2.2.
  221sparql_update(Request) :-
  222    memberchk(content_type(ContentType), Request),
  223    sub_atom(ContentType, 0, _, _, 'application/sparql-update'),
  224    !,
  225    http_parameters(Request,
  226                    [ 'using-graph-uri'(DefaultGraphs),
  227                      'using-named-graph-uri'(NamedGraphs),
  228                      format(ReqFormat),
  229                      entailment(Entailment)
  230                    ],
  231                    [attribute_declarations(sparql_decl)
  232                    ]),
  233    append(DefaultGraphs, NamedGraphs, Graphs),
  234    http_read_data(Request, Query, []),
  235    sparql_reply(Request, Query, Graphs, ReqFormat, Entailment).
  236% Perform a SPARQL update via POST with URL-encoded parameters.
  237% @compat SPARQL 1.1 Protocol recommendation, section 2.2.1.
  238sparql_update(Request) :-
  239    http_parameters(Request,
  240                    [ update(Query),
  241                      'using-graph-uri'(DefaultGraphs),
  242                      'using-named-graph-uri'(NamedGraphs),
  243                      format(ReqFormat),
  244                      entailment(Entailment)
  245                    ],
  246                    [ attribute_declarations(sparql_decl)
  247                    ]),
  248    append(DefaultGraphs, NamedGraphs, Graphs),
  249    sparql_reply(Request, Query, Graphs, ReqFormat, Entailment).
 sparql_reply(+Request, +Query, +_Graphs, +ReqFormat, +Entailment)
HTTP handler for SPARQL requests. Mounted the http-path sparql(.) (by default /sparql/, see library(http/http_path)).
  258sparql_reply(Request, Query, Graphs, ReqFormat, Entailment) :-
  259    statistics(cputime, CPU0),
  260    sparql_compile(Query, Compiled,
  261                   [ type(Type),
  262                     ordered(Ordered),
  263                     distinct(Distinct),
  264                     entailment(Entailment)
  265                   ]),
  266    (   Compiled = sparql_query(update(_), _, _)
  267    ->  authorized(write(Graphs, sparql))
  268    ;   true
  269    ),
  270    findall(R, sparql_run(Compiled, R), Rows),
  271    statistics(cputime, CPU1),
  272    CPU is CPU1 - CPU0,
  273    output_format(ReqFormat, Request, Format),
  274    write_result(Format, Type, Rows,
  275                 [ cputime(CPU),
  276                   ordered(Ordered),
  277                   distinct(Distinct)
  278                 ]).
  279
  280output_format(ReqFormat, Request, Format) :-
  281    var(ReqFormat),
  282    !,
  283    accept_output_format(Request, Format).
  284output_format('rdf+xml', _, xml) :- !.
  285output_format(json, _, json) :- !.
  286output_format(csv, _, csv) :- !.
  287output_format(Mime, _, Format) :-
  288    atomic_list_concat([Major,Minor], /, Mime),
  289    sparql_media(Major/Minor, Format),
  290    !.
  291
  292
  293accept_output_format(Request, Format) :-
  294    memberchk(accept(Accept), Request),
  295    (   atom(Accept)
  296    ->  http_parse_header_value(accept, Accept, Media)
  297    ;   Media = Accept
  298    ),
  299    find_media(Media, Format),
  300    !.
  301accept_output_format(_, xml).
  302
  303find_media([media(Type, _, _, _)|T], Format) :-
  304    (   sparql_media(Type, Format)
  305    ->  true
  306    ;   find_media(T, Format)
  307    ).
  308
  309sparql_media(application/'sparql-results+xml',   xml).
  310sparql_media(application/'sparql-results+json', json).
  311sparql_media(text/'tab-separated-values',        csv).
  312
  313write_result(xml, Type, Rows, Options) :-
  314    cors_enable,
  315    write_xml_result(Type, Rows, Options).
  316write_result(json, Type, Rows, Options) :-
  317    cors_enable,
  318    write_json_result(Type, Rows, Options).
  319write_result(csv, Type, Rows, Options) :-
  320    cors_enable,
  321    write_csv_result(Type, Rows, Options).
  322
  323write_xml_result(ask, [True], Options) :-
  324    !,
  325    format('Content-type: application/sparql-results+xml; charset=UTF-8~n~n'),
  326    sparql_write_xml_result(current_output, ask(True), Options).
  327write_xml_result(update, [True], Options) :-
  328    !,
  329    format('Content-type: application/sparql-results+xml; charset=UTF-8~n~n'),
  330    sparql_write_xml_result(current_output, update(True), Options).
  331write_xml_result(select(VarNames), Rows, Options) :-
  332    !,
  333    format('Transfer-encoding: chunked~n'),
  334    format('Content-type: application/sparql-results+xml; charset=UTF-8~n~n'),
  335    sparql_write_xml_result(current_output, select(VarNames, Rows), Options).
  336write_xml_result(_, RDF, _Options) :-
  337    format('Content-type: application/rdf+xml; charset=UTF-8~n~n'),
  338    rdf_write_xml(current_output, RDF).
  339
  340write_json_result(ask, [True], Options) :-
  341    !,
  342    sparql_write_json_result(current_output, ask(True), Options).
  343write_json_result(select(VarNames), Rows, Options) :-
  344    !,
  345    format('Transfer-encoding: chunked~n'),
  346    sparql_write_json_result(current_output, select(VarNames, Rows), Options).
  347write_json_result(_, _RDF, _Options) :-
  348    throw(http_reply(bad_request(format('JSON output is only supported for \c
  349                                             ASK and SELECT queries', [])))).
  350
  351write_csv_result(select(VarNames), Rows, Options) :-
  352    !,
  353    format('Transfer-encoding: chunked~n'),
  354    sparql_write_csv_result(current_output, select(VarNames, Rows), Options).
  355write_csv_result(_, _RDF, _Options) :-
  356    throw(http_reply(bad_request(format('CSV output is only supported for \c
  357                                             SELECT queries', [])))).
 sparql_decl(+OptionName, -Options)
Default options for specified attribute names. See http_parameters/3.
  365sparql_decl(query,
  366            [ description('The SPARQL query to execute')
  367            ]).
  368sparql_decl(update,
  369            [ description('The SPARQL update query to execute')
  370            ]).
  371sparql_decl('default-graph-uri',
  372            [ list(atom),
  373              description('The default graph(s) to query (not supported)')
  374            ]).
  375sparql_decl('named-graph-uri',
  376            [ list(atom),
  377              description('Additional named graph(s) to query (not supported)')
  378            ]).
  379sparql_decl('using-graph-uri',
  380            [ list(atom),
  381              description('The default graph(s) to update (not supported)')
  382            ]).
  383sparql_decl('using-named-graph-uri',
  384            [ list(atom),
  385              description('Additional named graph(s) to update (not supported)')
  386            ]).
  387sparql_decl(format,
  388            [ optional(true),
  389              oneof([ 'rdf+xml',
  390                      json,
  391                      csv,
  392                      'application/sparql-results+xml',
  393                      'application/sparql-results+json'
  394                    ]),
  395              description('Result format.  If not specified, the \c
  396                          HTTP Accept header is used')
  397            ]).
  398sparql_decl(entailment,
  399            [ optional(true),
  400              default(Default),
  401              oneof(Es),
  402              description('Entailment used')
  403            ]) :-
  404    setting(sparql:entailment, Default),
  405    findall(E, cliopatria:entailment(E, _), Es)