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@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2004-2010, University of Amsterdam,
    7			      VU University Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(api_sparql,
   32	  [
   33	  ]).   34:- use_module(user(user_db)).   35:- use_module(library(lists)).   36:- use_module(library(option)).   37:- use_module(library(uri)).   38:- use_module(library(rdf_write)).   39:- use_module(library(http/http_parameters)).   40:- use_module(library(http/http_client)).   41:- use_module(library(http/http_dispatch)).   42:- use_module(library(http/http_request_value)).   43:- use_module(library(http/http_cors)).   44:- use_module(library(http/html_write)).   45:- use_module(rdfql(sparql)).   46:- use_module(rdfql(sparql_xml_result)).   47:- use_module(rdfql(sparql_json_result)).   48:- use_module(rdfql(sparql_csv_result)).   49:- use_module(library(settings)).   50:- if(exists_source(applications(yasgui))).   51:- use_module(applications(yasgui)).   52:- endif.   53
   54% We serve both `/sparql/`  and  `/sparql`.   The  first  is  merely for
   55% historical reasons. Note that we cannot turn  a path alias into a path
   56% without a `/`, so we must use root(sparql) as a hack.
   57
   58:- http_handler(sparql(.),      sparql_query,  [spawn(sparql_query), id('sparql_query/')]).   59:- http_handler(root(sparql),   sparql_query,  [spawn(sparql_query), id(sparql_query)]).   60:- 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.
   98sparql_query(Request) :-
   99	empty_get_request(Request), !,
  100	redirect_human_form(Request).
  101% Perform a SPARQL query via GET.
  102% @compat SPARQL 1.1 Protocol recommendation, section 2.1.1.
  103sparql_query(Request) :-
  104	memberchk(method(get), Request), !,
  105	sparql_query_parameters(Request).
  106% Perform a SPARQL query via POST with encoded parameters in body.
  107% @compat SPARQL 1.1 Protocol recommendation, section 2.1.2.
  108sparql_query(Request) :-
  109	memberchk(method(post), Request),
  110	memberchk(content_type(ContentType), Request),
  111	sub_atom(ContentType, 0, _, _, 'application/x-www-form-urlencoded'), !,
  112	catch(sparql_query_parameters(Request), E, sparql_query_exception(E)).
  113% Perform a SPARQL query via POST with unencoded body.
  114% @compat SPARQL 1.1 Protocol recommendation, section 2.1.3.
  115sparql_query(Request) :-
  116	memberchk(method(post), Request),
  117	memberchk(content_type(ContentType), Request),
  118	sub_atom(ContentType, 0, _, _, 'application/sparql-query'), !,
  119	http_parameters(Request,
  120			[ 'default-graph-uri'(DefaultGraphs),
  121			  'named-graph-uri'(NamedGraphs),
  122			  format(ReqFormat),
  123			  entailment(Entailment)
  124			],
  125			[ attribute_declarations(sparql_decl)
  126			]),
  127	append(DefaultGraphs, NamedGraphs, Graphs),
  128	http_read_data(Request, Query, []),
  129	authorized(read(Graphs, sparql)),
  130	sparql_reply(Request, Query, Graphs, ReqFormat, Entailment).
  131sparql_query(_) :-
  132	throw(http_reply(bad_request(format('Unrecognized SPARQL query request.', [])))).
  133
  134sparql_query_parameters(Request) :-
  135	http_parameters(Request,
  136			[ query(Query),
  137			  'default-graph-uri'(DefaultGraphs),
  138			  'named-graph-uri'(NamedGraphs),
  139			  format(ReqFormat),
  140			  entailment(Entailment)
  141			],
  142			[ attribute_declarations(sparql_decl)
  143			]),
  144	append(DefaultGraphs, NamedGraphs, Graphs),
  145	authorized(read(Graphs, sparql)),
  146	sparql_reply(Request, Query, Graphs, ReqFormat, Entailment).
  147
  148sparql_query_exception(E) :-
  149	E = error(syntax_error(illegal_uri_query),_), !,
  150	throw(http_reply(bad_request(format('Malformed search parameters.', [])))).
  151sparql_query_exception(E) :-
  152	throw(E).
 empty_get_request(+Request) is semidet
True if Request is an HTTP GET request without any parameters.
  158empty_get_request(Request) :-
  159	option(request_uri(URI), Request),
  160	uri_components(URI, Components),
  161	uri_data(search, Components, Search),
  162	var(Search),
  163	option(method(get), Request).
  164
  165:- if(current_predicate(has_yasgui/0)).  166human_form_location(HREF) :-
  167	has_yasgui, !,
  168	http_link_to_id(yasgui, [], HREF).
  169:- endif.  170human_form_location(HREF) :-
  171	http_link_to_id(sparql_query_form, [], HREF).
  172
  173redirect_human_form(Request) :-
  174	human_form_location(HREF),
  175	reply_html_page(cliopatria(default),
  176			[ title('Redirect to SPARQL editor'),
  177			  meta([ 'http-equiv'(refresh),
  178				 content('5; url='+HREF)
  179			       ])
  180			], \sparql_redirect_explanation(Request, HREF)).
  181
  182sparql_redirect_explanation(Request, EditorHREF) -->
  183	{ option(request_uri(URI), Request) },
  184	html({|html(URI, EditorHREF)||
  185<h4>Redirecting to SPARQL editor ...</h4>
  186
  187<div class="warning" style="width:80%;margin:auto;border:1px solid #888;padding: 10px 5px">
  188You have landed in the SPARQL access location <a href=URI>URI</a> of this server.
  189<b>This URI is intended for machines</b>.  Because your request contains no parameters,
  190you will be redirected to the SPARQL editor at <a href=EditorHREF>EditorHREF</a>
  191in 5 seconds.
  192</div>
  193	     |}).
 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.
  203% Browser pointed here
  204sparql_update(Request) :-
  205	empty_get_request(Request), !,
  206	redirect_human_form(Request).
  207% Perform a SPARQL update via POST directly.
  208% @compat SPARQL 1.1 Protocol recommendation, section 2.2.2.
  209sparql_update(Request) :-
  210	memberchk(content_type(ContentType), Request),
  211	sub_atom(ContentType, 0, _, _, 'application/sparql-update'), !,
  212	http_parameters(Request,
  213			[ 'using-graph-uri'(DefaultGraphs),
  214			  'using-named-graph-uri'(NamedGraphs),
  215			  format(ReqFormat),
  216			  entailment(Entailment)
  217			],
  218			[attribute_declarations(sparql_decl)
  219			]),
  220	append(DefaultGraphs, NamedGraphs, Graphs),
  221	http_read_data(Request, Query, []),
  222	sparql_reply(Request, Query, Graphs, ReqFormat, Entailment).
  223% Perform a SPARQL update via POST with URL-encoded parameters.
  224% @compat SPARQL 1.1 Protocol recommendation, section 2.2.1.
  225sparql_update(Request) :-
  226	http_parameters(Request,
  227			[ update(Query),
  228			  'using-graph-uri'(DefaultGraphs),
  229			  'using-named-graph-uri'(NamedGraphs),
  230			  format(ReqFormat),
  231			  entailment(Entailment)
  232			],
  233			[ attribute_declarations(sparql_decl)
  234			]),
  235	append(DefaultGraphs, NamedGraphs, Graphs),
  236	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)).
  245sparql_reply(Request, Query, Graphs, ReqFormat, Entailment) :-
  246	statistics(cputime, CPU0),
  247	sparql_compile(Query, Compiled,
  248		       [ type(Type),
  249			 ordered(Ordered),
  250			 distinct(Distinct),
  251			 entailment(Entailment)
  252		       ]),
  253	(   Compiled = sparql_query(update(_), _, _)
  254	->  authorized(write(Graphs, sparql))
  255	;   true
  256	),
  257	findall(R, sparql_run(Compiled, R), Rows),
  258	statistics(cputime, CPU1),
  259	CPU is CPU1 - CPU0,
  260	output_format(ReqFormat, Request, Format),
  261	write_result(Format, Type, Rows,
  262		     [ cputime(CPU),
  263		       ordered(Ordered),
  264		       distinct(Distinct)
  265		     ]).
  266
  267output_format(ReqFormat, Request, Format) :-
  268	var(ReqFormat), !,
  269	accept_output_format(Request, Format).
  270output_format('rdf+xml', _, xml) :- !.
  271output_format(json, _, json) :- !.
  272output_format(csv, _, csv) :- !.
  273output_format(Mime, _, Format) :-
  274	atomic_list_concat([Major,Minor], /, Mime),
  275	sparql_media(Major/Minor, Format), !.
  276
  277
  278accept_output_format(Request, Format) :-
  279	memberchk(accept(Accept), Request),
  280	(   atom(Accept)
  281	->  http_parse_header_value(accept, Accept, Media)
  282	;   Media = Accept
  283	),
  284	find_media(Media, Format), !.
  285accept_output_format(_, xml).
  286
  287find_media([media(Type, _, _, _)|T], Format) :-
  288	(   sparql_media(Type, Format)
  289	->  true
  290	;   find_media(T, Format)
  291	).
  292
  293sparql_media(application/'sparql-results+xml',   xml).
  294sparql_media(application/'sparql-results+json', json).
  295sparql_media(text/'tab-separated-values',	 csv).
  296
  297write_result(xml, Type, Rows, Options) :-
  298	cors_enable,
  299	write_xml_result(Type, Rows, Options).
  300write_result(json, Type, Rows, Options) :-
  301	cors_enable,
  302	write_json_result(Type, Rows, Options).
  303write_result(csv, Type, Rows, Options) :-
  304	cors_enable,
  305	write_csv_result(Type, Rows, Options).
  306
  307write_xml_result(ask, [True], Options) :- !,
  308	format('Content-type: application/sparql-results+xml; charset=UTF-8~n~n'),
  309	sparql_write_xml_result(current_output, ask(True), Options).
  310write_xml_result(update, [True], Options) :- !,
  311	format('Content-type: application/sparql-results+xml; charset=UTF-8~n~n'),
  312	sparql_write_xml_result(current_output, update(True), Options).
  313write_xml_result(select(VarNames), Rows, Options) :- !,
  314	format('Transfer-encoding: chunked~n'),
  315	format('Content-type: application/sparql-results+xml; charset=UTF-8~n~n'),
  316	sparql_write_xml_result(current_output, select(VarNames, Rows), Options).
  317write_xml_result(_, RDF, _Options) :-
  318	format('Content-type: application/rdf+xml; charset=UTF-8~n~n'),
  319	rdf_write_xml(current_output, RDF).
  320
  321write_json_result(ask, [True], Options) :- !,
  322	sparql_write_json_result(current_output, ask(True), Options).
  323write_json_result(select(VarNames), Rows, Options) :- !,
  324	format('Transfer-encoding: chunked~n'),
  325	sparql_write_json_result(current_output, select(VarNames, Rows), Options).
  326write_json_result(_, _RDF, _Options) :-
  327	throw(http_reply(bad_request(format('JSON output is only supported for \c
  328					     ASK and SELECT queries', [])))).
  329
  330write_csv_result(select(VarNames), Rows, Options) :- !,
  331	format('Transfer-encoding: chunked~n'),
  332	sparql_write_csv_result(current_output, select(VarNames, Rows), Options).
  333write_csv_result(_, _RDF, _Options) :-
  334	throw(http_reply(bad_request(format('CSV output is only supported for \c
  335					     SELECT queries', [])))).
 sparql_decl(+OptionName, -Options)
Default options for specified attribute names. See http_parameters/3.
  343sparql_decl(query,
  344	    [ description('The SPARQL query to execute')
  345	    ]).
  346sparql_decl(update,
  347	    [ description('The SPARQL update query to execute')
  348	    ]).
  349sparql_decl('default-graph-uri',
  350	    [ list(atom),
  351	      description('The default graph(s) to query (not supported)')
  352	    ]).
  353sparql_decl('named-graph-uri',
  354	    [ list(atom),
  355	      description('Additional named graph(s) to query (not supported)')
  356	    ]).
  357sparql_decl('using-graph-uri',
  358	    [ list(atom),
  359	      description('The default graph(s) to update (not supported)')
  360	    ]).
  361sparql_decl('using-named-graph-uri',
  362	    [ list(atom),
  363	      description('Additional named graph(s) to update (not supported)')
  364	    ]).
  365sparql_decl(format,
  366	    [ optional(true),
  367	      oneof([ 'rdf+xml',
  368		      json,
  369		      csv,
  370		      'application/sparql-results+xml',
  371		      'application/sparql-results+json'
  372		    ]),
  373	      description('Result format.  If not specified, the \c
  374			  HTTP Accept header is used')
  375	    ]).
  376sparql_decl(entailment,
  377	    [ optional(true),
  378	      default(Default),
  379	      oneof(Es),
  380	      description('Entailment used')
  381	    ]) :-
  382	setting(sparql:entailment, Default),
  383	findall(E, cliopatria:entailment(E, _), Es)