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-2015, 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_sesame,
   32	  [ api_action/4		% +Request, +Goal, +Format, +Message
   33	  ]).   34:- use_module(rdfql(serql)).   35:- use_module(rdfql(sparql)).   36:- use_module(rdfql(rdf_io)).   37:- use_module(rdfql(rdf_html)).   38:- use_module(library(http/http_parameters)).   39:- use_module(user(user_db)).   40:- use_module(library(semweb/rdfs)).   41:- use_module(library(semweb/rdf_db)).   42:- use_module(library(semweb/rdf_http_plugin)).   43:- use_module(library(semweb/rdf_file_type)).   44:- use_module(library(semweb/rdf_persistency)).   45:- use_module(library(http/html_write)).   46:- use_module(library(http/http_request_value)).   47:- use_module(library(http/http_dispatch)).   48:- use_module(library(http/http_client)).   49:- use_module(library(http/http_open)).   50:- use_module(library(http/json)).   51:- use_module(library(memfile)).   52:- use_module(library(debug)).   53:- use_module(library(lists)).   54:- use_module(library(option)).   55:- use_module(library(apply)).   56:- use_module(library(settings)).   57:- use_module(components(query)).   58:- use_module(components(basics)).   59:- use_module(components(messages)).   60
   61:- meta_predicate(api_action2(+,0,+,+)).   62
   63:- http_handler(sesame('login'),	      http_login,	    []).   64:- http_handler(sesame('logout'),	      http_logout,	    []).   65:- http_handler(sesame('evaluateQuery'),      evaluate_query,
   66		[spawn(sparql_query)]).   67:- http_handler(sesame('evaluateGraphQuery'), evaluate_graph_query,
   68		[spawn(sparql_query)]).   69:- http_handler(sesame('evaluateTableQuery'), evaluate_table_query,
   70		[spawn(sparql_query)]).   71:- http_handler(sesame('extractRDF'),	      extract_rdf,	    []).   72:- http_handler(sesame('listRepositories'),   list_repositories,    []).   73:- http_handler(sesame('clearRepository'),    clear_repository,	    []).   74:- http_handler(sesame('unloadSource'),	      unload_source,
   75		[ time_limit(infinite) ]).   76:- http_handler(sesame('unloadGraph'),	      unload_graph,
   77		[ time_limit(infinite) ]).   78:- http_handler(sesame('uploadData'),	      upload_data,
   79		[ time_limit(infinite) ]).   80:- http_handler(sesame('uploadURL'),	      upload_url,
   81		[ time_limit(infinite) ]).   82:- http_handler(sesame('removeStatements'),   remove_statements,
   83		[ time_limit(infinite) ]).   84:- http_handler(sesame('flushJournal'),	      flush_journal,
   85		[ time_limit(infinite) ]).   86:- http_handler(sesame('modifyPersistency'),  modify_persistency,
   87		[ time_limit(infinite) ]).   88:- http_handler(sesame('addPrefix'),	      add_prefix,
   89		[ time_limit(infinite) ]).   90
   91:- html_meta
   92	api_action(+, 0, +, html).
 http_login(+Request)
HTTP handler to associate the current session with a local user. If the login succeeds a 200 reply according to the resultFormat parameters is sent. If the result fails due to a wrong user/password, the server responds with a 403 (forbidden) message. Other failures result in a 500 (server error).
See also
- help('howto/ClientAuth.txt') for additional information on authetication.
  105http_login(Request) :-
  106	http_parameters(Request,
  107			[ user(User),
  108			  password(Password),
  109			  resultFormat(ResultFormat)
  110			],
  111			[ attribute_declarations(attribute_decl)
  112			]),
  113	result_format(Request, ResultFormat),
  114	api_action(Request,
  115		   (   validate_login(Request, User, Password),
  116		       login(User)
  117		   ),
  118		   ResultFormat,
  119		   'Login ~w'-[User]).
  120
  121validate_login(_, User, Password) :-
  122	validate_password(User, Password), !.
  123validate_login(Request, _, _) :-
  124	memberchk(path(Path), Request),
  125	throw(http_reply(forbidden(Path))).
 http_logout(+Request)
HTTP handler to logout current user.
  132http_logout(Request) :-
  133	http_parameters(Request,
  134			[ resultFormat(ResultFormat)
  135			],
  136			[ attribute_declarations(attribute_decl)
  137			]),
  138	result_format(Request, ResultFormat),
  139	api_action(Request,
  140		   logout_user(Message),
  141		   ResultFormat,
  142		   Message).
  143
  144logout_user('Logout ~w'-[User]) :-
  145	logged_on(User), !,
  146	logout(User).
  147logout_user('Not logged on'-[]).
 evaluate_query(+Request) is det
HTTP handler for both SeRQL and SPARQL queries. This handler deals with interactive queries. Machines typically access /sparql/ to submit queries and process result compliant to the SPARQL protocol.
  157evaluate_query(Request) :-
  158	http_parameters(Request,
  159			[ repository(Repository),
  160			  query(Query),
  161			  queryLanguage(QueryLanguage),
  162			  resultFormat(ResultFormat),
  163			  serialization(Serialization),
  164			  resourceFormat(ResourceFormat),
  165			  entailment(Entailment),
  166			  storeAs(SaveAs)
  167			],
  168			[ attribute_declarations(attribute_decl)
  169			]),
  170	result_format(Request, ResultFormat),
  171	statistics(cputime, CPU0),
  172	downcase_atom(QueryLanguage, QLang),
  173	compile(QLang, Query, Compiled,
  174		[ entailment(Entailment),
  175		  type(Type)
  176		]),
  177	authorized_query(Type, Repository, ResultFormat),
  178	findall(Reply, run(QLang, Compiled, Reply), Result),
  179	statistics(cputime, CPU1),
  180	CPU is CPU1 - CPU0,
  181	store_query(construct, SaveAs, Query),
  182	(   graph_type(Type)
  183	->  write_graph(Result,
  184			[ result_format(ResultFormat),
  185			  serialization(Serialization),
  186			  resource_format(ResourceFormat),
  187			  cputime(CPU)
  188			])
  189	;   Type = select(VarNames)
  190	->  write_table(Result,
  191			[ variables(VarNames),
  192			  result_format(ResultFormat),
  193			  serialization(Serialization),
  194			  resource_format(ResourceFormat),
  195			  cputime(CPU)
  196			])
  197	;   Type == ask, Result = [Reply]
  198	->  reply_html_page(cliopatria(default),
  199			    title('ASK Result'),
  200			    [ h4('ASK query completed'),
  201			      p(['Answer = ', Reply])
  202			    ])
  203	;   Type == update, Result = [Reply]
  204	->  reply_html_page(cliopatria(default),
  205			    title('Update Result'),
  206			    [ h4('Update query completed'),
  207			      p(['Answer = ', Reply])
  208			    ])
  209	).
  210
  211
  212authorized_query(update, Repository, ResultFormat) :- !,
  213	authorized_api(write(Repository, sparql(update)), ResultFormat).
  214authorized_query(_, Repository, ResultFormat) :-
  215	authorized_api(read(Repository, query), ResultFormat).
 evaluate_graph_query(+Request)
Handle CONSTRUCT queries.
  221evaluate_graph_query(Request) :-
  222	http_parameters(Request,
  223			[ repository(Repository),
  224			  query(Query),
  225			  queryLanguage(QueryLanguage),
  226			  resultFormat(ResultFormat),
  227			  serialization(Serialization),
  228			  resourceFormat(ResourceFormat),
  229			  entailment(Entailment),
  230			  storeAs(SaveAs)
  231			],
  232			[ attribute_declarations(attribute_decl)
  233			]),
  234	result_format(Request, ResultFormat),
  235	authorized_api(read(Repository, query), ResultFormat),
  236	statistics(cputime, CPU0),
  237	downcase_atom(QueryLanguage, QLang),
  238	compile(QLang, Query, Compiled,
  239		[ entailment(Entailment),
  240		  type(Type)
  241		]),
  242	(   graph_type(Type)
  243	->  true
  244	;   throw(error(domain_error(query_type(graph), Type), _))
  245	),
  246	findall(T, run(QLang, Compiled, T), Triples),
  247	statistics(cputime, CPU1),
  248	store_query(construct, SaveAs, Query),
  249	CPU is CPU1 - CPU0,
  250	write_graph(Triples,
  251		    [ result_format(ResultFormat),
  252		      serialization(Serialization),
  253		      resource_format(ResourceFormat),
  254		      cputime(CPU)
  255		    ]).
  256
  257graph_type(construct).
  258graph_type(describe).
 evaluate_table_query(+Request)
Handle SELECT queries.
  264evaluate_table_query(Request) :-
  265	http_parameters(Request,
  266			[ repository(Repository),
  267			  query(Query),
  268			  queryLanguage(QueryLanguage),
  269			  resultFormat(ResultFormat),
  270			  serialization(Serialization),
  271			  resourceFormat(ResourceFormat),
  272			  entailment(Entailment),
  273			  storeAs(SaveAs)
  274			],
  275			[ attribute_declarations(attribute_decl)
  276			]),
  277	result_format(Request, ResultFormat),
  278	authorized_api(read(Repository, query), ResultFormat),
  279	statistics(cputime, CPU0),
  280	downcase_atom(QueryLanguage, QLang),
  281	compile(QLang, Query, Compiled,
  282		[ entailment(Entailment),
  283		  type(select(VarNames))
  284		]),
  285	findall(R, run(QLang, Compiled, R), Rows),
  286	statistics(cputime, CPU1),
  287	CPU is CPU1 - CPU0,
  288	store_query(select, SaveAs, Query),
  289	write_table(Rows,
  290		    [ variables(VarNames),
  291		      result_format(ResultFormat),
  292		      serialization(Serialization),
  293		      resource_format(ResourceFormat),
  294		      cputime(CPU)
  295		    ]).
 compile(+Language, +Query, -Compiled, +Options)
Compile a query and validate the query-type
  301compile(serql, Query, Compiled, Options) :- !,
  302	serql_compile(Query, Compiled, Options).
  303compile(sparql, Query, Compiled, Options) :- !,
  304	sparql_compile(Query, Compiled, Options).
  305compile(Language, _, _, _) :-
  306	throw(error(domain_error(query_language, Language), _)).
 run(+Language, +Compiled, -Reply)
  310run(serql, Compiled, Reply) :-
  311	serql_run(Compiled, Reply).
  312run(sparql, Compiled, Reply) :-
  313	sparql_run(Compiled, Reply).
 extract_rdf(+Request)
HTTP handler to extract RDF from the database. This handler separates the data into schema data and non-schema data, where schema data are triples whose subject is an rdfs:Class or rdf:Property. By default both are off, so one needs to pass either or both of the schema and data options as on.
  323extract_rdf(Request) :-
  324	http_parameters(Request,
  325			[ repository(Repository),
  326			  schema(Schema),
  327			  data(Data),
  328			  explicitOnly(ExplicitOnly),
  329			  niceOutput(_NiceOutput),
  330			  serialization(Serialization)
  331			],
  332			[ attribute_declarations(attribute_decl)
  333			]),
  334	authorized(read(Repository, download)),
  335	statistics(cputime, CPU0),
  336	findall(T, export_triple(Schema, Data, ExplicitOnly, T), Triples),
  337	statistics(cputime, CPU1),
  338	CPU is CPU1 - CPU0,
  339	write_graph(Triples,
  340		    [ serialization(Serialization),
  341		      cputime(CPU)
  342		    ]).
 export_triple(+Schema, +Data, +ExplicitOnly, -RDF)
  347export_triple(off, off, _, _) :- !,
  348	fail.				% no data requested
  349export_triple(on, on, on, rdf(S,P,O)) :- !,
  350	rdf_db:rdf(S,P,O).
  351export_triple(on, on, off, rdf(S,P,O)) :- !,
  352	rdfs_entailment:rdf(S,P,O).
  353export_triple(off, on, Explicit, RDF) :-
  354	export_triple(on, on, Explicit, RDF),
  355	\+ schema_triple(RDF).
  356export_triple(on, off, Explicit, RDF) :-
  357	export_triple(on, on, Explicit, RDF),
  358	schema_triple(RDF).
  359
  360schema_triple(rdf(S,_P,_O)) :-
  361	rdfs_individual_of(S, rdf:'Property').
  362schema_triple(rdf(S,_P,_O)) :-
  363	rdfs_individual_of(S, rdfs:'Class').
 list_repositories(+Request)
List the available repositories. This is only default for now
  370list_repositories(_Request) :-
  371	Repository = default,
  372	logged_on(User, anonymous),
  373	(   catch(check_permission(User, write(Repository, _)), _, fail)
  374	->  Write = true
  375	;   Write = false
  376	),
  377	(   catch(check_permission(User, read(Repository, _)), _, fail)
  378	->  Read = true
  379	;   Read = false
  380	),
  381	format('Content-type: text/xml~n~n'),
  382	format('<?xml version="1.0" encoding="ISO-8859-1"?>~n~n', []),
  383	format('<repositorylist>~n'),
  384	format('  <repository id="default" readable="~w" writeable="~w">~n',
  385	       [ Read, Write ]),
  386	format('    <title>Default repository</title>~n'),
  387	format('  </repository>~n'),
  388	format('</repositorylist>~n').
 clear_repository(+Request)
Clear the repository.
  395clear_repository(Request) :-
  396	http_parameters(Request,
  397			[ repository(Repository),
  398			  resultFormat(ResultFormat)
  399			],
  400			[ attribute_declarations(attribute_decl)
  401			]),
  402	result_format(Request, ResultFormat),
  403	authorized_api(write(Repository, clear), ResultFormat),
  404	api_action(Request,
  405		   rdf_reset_db,
  406		   ResultFormat,
  407		   'Clear database'-[]).
 unload_source(+Request)
Remove triples loaded from a specified source
  413unload_source(Request) :-
  414	http_parameters(Request,
  415			[ repository(Repository),
  416			  source(Source),
  417			  resultFormat(ResultFormat)
  418			],
  419			[ attribute_declarations(attribute_decl)
  420			]),
  421	result_format(Request, ResultFormat),
  422	authorized_api(write(Repository, unload(Source)), ResultFormat),
  423	api_action(Request, rdf_unload(Source),
  424		   ResultFormat,
  425		   'Unload triples from ~w'-[Source]).
 unload_graph(+Request)
Remove a named graph.
  432unload_graph(Request) :-
  433	http_parameters(Request,
  434			[ repository(Repository),
  435			  graph(Graph, []),
  436			  resultFormat(ResultFormat)
  437			],
  438			[ attribute_declarations(attribute_decl)
  439			]),
  440	result_format(Request, ResultFormat),
  441	authorized_api(write(Repository, unload(Graph)), ResultFormat),
  442	api_action(Request, rdf_unload_graph(Graph),
  443		   ResultFormat,
  444		   'Unload triples from ~w'-[Graph]).
 flush_journal(+Request)
Flush the journal of the requested graph
  451flush_journal(Request) :-
  452	http_parameters(Request,
  453			[ repository(Repository),
  454			  graph(Graph, []),
  455			  resultFormat(ResultFormat)
  456			],
  457			[ attribute_declarations(attribute_decl)
  458			]),
  459	result_format(Request, ResultFormat),
  460	authorized_api(write(Repository, unload(Graph)), ResultFormat),
  461	api_action(Request, rdf_flush_journals([graph(Graph)]),
  462		   ResultFormat,
  463		   'Flushed journals for graph ~w'-[Graph]).
 modify_persistency(+Request)
Change the persistent properties for the requested graph
  470modify_persistency(Request) :-
  471	http_parameters(Request,
  472			[ repository(Repository),
  473			  graph(Graph, []),
  474			  resultFormat(ResultFormat),
  475			  persistent(Persistent)
  476			],
  477			[ attribute_declarations(attribute_decl)
  478			]),
  479	persistency(Persistent, PVal, Action),
  480	result_format(Request, ResultFormat),
  481	authorized_api(write(Repository, persistent(Graph)), ResultFormat),
  482	api_action(Request, rdf_persistency(Graph, PVal),
  483		   ResultFormat,
  484		   '~w persistency for graph ~w'-[Action, Graph]).
  485
  486persistency(on,  true,  'Set').
  487persistency(off, false, 'Cleared').
 upload_data(Request)
Sesame compliant method to upload data to the repository, typically used to handle a POST-form from a web-browser (e.g., Load local file in the ClioPatria menu). If dataFormat is omitted, the format of the data is guessed from the data itself. Currently, this possitively identifies valid RDF/XML and assumes that anything else is Turtle.
  499:- if(current_predicate(http_convert_parameters/3)).
 create_tmp_file(+Stream, -Out, +Options) is det
Called from library(http/http_multipart_plugin) to process uploaded file from a form.
Arguments:
Stream- is the input stream. It signals EOF at the end of the part, but must not be closed.
Options- provides information about the part. Typically, this contains filename(FileName) and optionally media(Type, MediaParams).
  511:- public create_tmp_file/3.  512create_tmp_file(Stream, file(File, Options), Options) :-
  513	setup_call_catcher_cleanup(
  514	    tmp_file_stream(binary, File, Out),
  515	    copy_stream_data(Stream, Out),
  516	    Why,
  517	    cleanup(Why, File, Out)).
  518
  519cleanup(Why, File, Out) :-
  520	close(Out),
  521	(   Why == exit
  522	->  true
  523	;   catch(delete_file(File), _, true)
  524	).
 upload_data_file(+Request, +FormData, +TempFile, +FileOptions)
Load RDF from TempFile with additional form data provided in FormData. Options are the options passed from the uploaded file and include filename(Name) and optionally media(Type, Params).
  532upload_data_file(Request, Data, TmpFile, FileOptions) :-
  533	http_convert_parameters(Data,
  534				[ repository(Repository),
  535				  dataFormat(DataFormat),
  536				  baseURI(BaseURI),
  537				  verifyData(_Verify),
  538				  resultFormat(ResultFormat)
  539				],
  540				attribute_decl),
  541	result_format(Request, ResultFormat),
  542	authorized_api(write(Repository, load(posted)), ResultFormat),
  543	phrase(load_option(DataFormat, BaseURI), LoadOptions),
  544	append(LoadOptions, FileOptions, Options),
  545	api_action(Request,
  546		   setup_call_cleanup(
  547		       open(TmpFile, read, Stream),
  548		       rdf_guess_format_and_load(Stream, Options),
  549		       close(Stream)),
  550		   ResultFormat,
  551		   'Load data from POST'-[]).
  552
  553upload_option(_=_) :- !.
  554upload_option(Term) :- functor(Term, _, 1).
  555
  556upload_data(Request) :-
  557	option(method(post), Request), !,
  558	http_read_data(Request, Data,
  559		       [ on_filename(create_tmp_file)
  560		       ]),
  561	(   option(data(file(TmpFile, FileOptions)), Data)
  562	->  true
  563	;   existence_error(attribute_declaration, data)
  564	),
  565	include(upload_option, FileOptions, Options),
  566	call_cleanup(upload_data_file(Request, Data, TmpFile, Options),
  567		     catch(delete_file(TmpFile), _, true)).
  568
  569:- endif.  570upload_data(Request) :-
  571	http_parameters(Request,
  572			[ repository(Repository),
  573			  data(Data,
  574			       [ description('RDF data to be loaded')
  575			       ]),
  576			  dataFormat(DataFormat),
  577			  baseURI(BaseURI),
  578			  verifyData(_Verify),
  579			  resultFormat(ResultFormat)
  580			],
  581			[ attribute_declarations(attribute_decl)
  582			]),
  583	result_format(Request, ResultFormat),
  584	authorized_api(write(Repository, load(posted)), ResultFormat),
  585	phrase(load_option(DataFormat, BaseURI), Options),
  586	atom_to_memory_file(Data, MemFile),
  587	api_action(Request,
  588		   setup_call_cleanup(open_memory_file(MemFile, read, Stream),
  589				      rdf_guess_format_and_load(Stream, Options),
  590				      ( close(Stream),
  591					free_memory_file(MemFile)
  592				      )),
  593		   ResultFormat,
  594		   'Load data from POST'-[]).
 upload_url(+Request)
Load data from an HTTP server. This API is compatible to Sesame, although the verifyData option is not implemented (data is always checked for syntax). Unlike Sesame, the default format is not rdfxml, but derived from the Content-type reported by the server.
See also
- Calls rdf_load/2 for the actual loading.
- load_url_form/1 a form to access this API
  607upload_url(Request) :-
  608	http_parameters(Request,
  609			[ url(URL, []),
  610			  dataFormat(DataFormat),
  611			  baseURI(BaseURI,
  612				  [ default(URL)
  613				  ]),
  614			  resultFormat(ResultFormat),
  615			  verifyData(_Verify),
  616			  repository(Repository)
  617			],
  618			[ attribute_declarations(attribute_decl)
  619			]),
  620	result_format(Request, ResultFormat),
  621	authorized_api(write(Repository, load(url(URL))), ResultFormat),
  622	phrase(load_option(DataFormat, BaseURI), Options),
  623	api_action(Request,
  624		   load_from_url(URL, Options),
  625		   ResultFormat,
  626		   'Load data from ~w'-[URL]).
  627
  628load_from_url(URL, Options) :-
  629	http_open(URL, In,
  630		  [ cert_verify_hook(ssl_verify)
  631		  ]),
  632	call_cleanup(rdf_guess_format_and_load(In, Options),
  633		     close(In)).
  634
  635:- public ssl_verify/5.
 ssl_verify(+SSL, +ProblemCert, +AllCerts, +FirstCert, +Error)
Currently we accept all certificates. We organise our own security using SHA1 signatures, so we do not care about the source of the data.
  643ssl_verify(_SSL,
  644	   _ProblemCertificate, _AllCertificates, _FirstCertificate,
  645	   _Error).
  646
  647load_option(DataFormat, BaseURI) -->
  648	data_format_option(DataFormat),
  649	base_uri_option(BaseURI).
  650
  651data_format_option(Var)      --> {var(Var)}, !.
  652data_format_option(rdfxml)   --> [format(xml)].
  653data_format_option(ntriples) --> [format(turtle)].
  654data_format_option(turtle)   --> [format(turtle)].
  655
  656base_uri_option(Var) --> {var(Var)}, !.
  657base_uri_option(URI) --> [base_uri(URI)].
 remove_statements(+Request)
Remove statements from the database
  664remove_statements(Request) :-
  665	http_parameters(Request,
  666			[ repository(Repository, [optional(true)]),
  667			  resultFormat(ResultFormat),
  668					% as documented
  669			  subject(Subject, [optional(true)]),
  670			  predicate(Predicate, [optional(true)]),
  671			  object(Object, [optional(true)]),
  672					% remove (turtle) graph
  673			  baseURI(BaseURI),
  674			  dataFormat(DataFormat),
  675			  data(Data, [optional(true)])
  676			],
  677			[ attribute_declarations(attribute_decl)
  678			]),
  679	result_format(Request, ResultFormat),
  680	instantiated(Subject, SI),
  681	instantiated(Predicate, PI),
  682	instantiated(Object, OI),
  683	authorized_api(write(Repository, remove_statements(SI, PI, OI)),
  684		       ResultFormat),
  685
  686	(   nonvar(Data)
  687	->  setup_call_cleanup(( atom_to_memory_file(Data, MemFile),
  688				 open_memory_file(MemFile, read, Stream,
  689						  [ free_on_close(true)
  690						  ])
  691			       ),
  692			       ( rdf_guess_data_format(Stream, DataFormat),
  693			         get_triples(stream(Stream),
  694					     Triples,
  695					     [ base_uri(BaseURI),
  696					       data_format(DataFormat)
  697					     ])
  698			       ),
  699			       close(Stream)),
  700	    length(Triples, NTriples),
  701	    debug(removeStatements, 'Removing ~D statements', [NTriples]),
  702	    api_action(Request,
  703		       remove_triples(Triples),
  704		       ResultFormat,
  705		       'Remove ~D triples'-[NTriples])
  706	;   debug(removeStatements, 'removeStatements = ~w',
  707		  [rdf(Subject, Predicate, Object)]),
  708
  709	    ntriple_part(Subject,   subject,   S),
  710	    ntriple_part(Predicate, predicate, P),
  711	    ntriple_part(Object,    object,    O),
  712
  713	    debug(removeStatements, 'Action = ~q', [rdf_retractall(S,P,O)]),
  714	    api_action(Request,
  715		       rdf_retractall(S,P,O),
  716		       ResultFormat,
  717		       'Remove statements from ~k'-[rdf(S,P,O)])
  718	).
 remove_triples(+List)
Remove indicated triples from the database.
  724remove_triples([]).
  725remove_triples([rdf(S,P,O)|T]) :-
  726	rdf_retractall(S,P,O),
  727	remove_triples(T).
  728
  729instantiated(X, I) :-
  730	(   var(X)
  731	->  I = (-)
  732	;   I = (+)
  733	).
  734
  735ntriple_part(In, _, _) :-
  736	var(In), !.
  737ntriple_part('', _, _) :- !.
  738ntriple_part(In, Field, Out) :-
  739	atom_codes(In, Codes),
  740	phrase(rdf_ntriple_part(Field, Out), Codes), !.
  741ntriple_part(Text, Field, _) :-
  742	throw(error(type_error(ntriples(Field), Text),
  743		    context(_,
  744			    'Field must be in N-triples notation'))).
 rdf_ntriple_part(+Type, -Value)//
Parse one of the fields of an ntriple. This is used for the SWI-Prolog Sesame (rdf4j.org) implementation to realise /servlets/removeStatements. I do not think public use of this predicate should be stimulated.
  754rdf_ntriple_part(subject, Subject) -->
  755	subject(Subject).
  756rdf_ntriple_part(predicate, Predicate) -->
  757	predicate(Predicate).
  758rdf_ntriple_part(object, Object) -->
  759	object(Object).
  760
  761subject(Subject) -->
  762	uniref(Subject), !.
  763subject(Subject) -->
  764	node_id(Subject).
  765
  766predicate(Predicate) -->
  767	uniref(Predicate).
  768
  769object(Object) -->
  770	uniref(Object), !.
  771object(Object) -->
  772	node_id(Object).
  773object(Object) -->
  774	literal(Object).
  775
  776
  777uniref(URI) -->
  778	"<",
  779	escaped_uri_codes(Codes),
  780	">", !,
  781	{ atom_codes(URI, Codes)
  782	}.
  783
  784node_id(node(Id)) -->			% anonymous nodes
  785	"_:",
  786	name_start(C0),
  787	name_codes(Codes),
  788	{ atom_codes(Id, [C0|Codes])
  789	}.
  790
  791literal(Literal) -->
  792	lang_string(Literal), !.
  793literal(Literal) -->
  794	xml_string(Literal).
  795
  796
  797%	name_start(-Code)
  798%	name_codes(-ListfCodes)
  799%
  800%	Parse identifier names
  801
  802name_start(C) -->
  803	[C],
  804	{ code_type(C, alpha)
  805	}.
  806
  807name_codes([C|T]) -->
  808	[C],
  809	{ code_type(C, alnum)
  810	}, !,
  811	name_codes(T).
  812name_codes([]) -->
  813	[].
  814
  815
  816%	escaped_uri_codes(-CodeList)
  817%
  818%	Decode string holding %xx escaped characters.
  819
  820escaped_uri_codes([]) -->
  821	[].
  822escaped_uri_codes([C|T]) -->
  823	"%", [D0,D1], !,
  824	{ code_type(D0, xdigit(V0)),
  825	  code_type(D1, xdigit(V1)),
  826	  C is V0<<4 + V1
  827	},
  828	escaped_uri_codes(T).
  829escaped_uri_codes([C|T]) -->
  830	"\\u", [D0,D1,D2,D3], !,
  831	{ code_type(D0, xdigit(V0)),
  832	  code_type(D1, xdigit(V1)),
  833	  code_type(D2, xdigit(V2)),
  834	  code_type(D3, xdigit(V3)),
  835	  C is V0<<12 + V1<<8 + V2<<4 + V3
  836	},
  837	escaped_uri_codes(T).
  838escaped_uri_codes([C|T]) -->
  839	"\\U", [D0,D1,D2,D3,D4,D5,D6,D7], !,
  840	{ code_type(D0, xdigit(V0)),
  841	  code_type(D1, xdigit(V1)),
  842	  code_type(D2, xdigit(V2)),
  843	  code_type(D3, xdigit(V3)),
  844	  code_type(D4, xdigit(V4)),
  845	  code_type(D5, xdigit(V5)),
  846	  code_type(D6, xdigit(V6)),
  847	  code_type(D7, xdigit(V7)),
  848	  C is V0<<28 + V1<<24 + V2<<20 + V3<<16 +
  849	       V4<<12 + V5<<8 + V6<<4 + V7
  850	},
  851	escaped_uri_codes(T).
  852escaped_uri_codes([C|T]) -->
  853	[C],
  854	escaped_uri_codes(T).
  855
  856%	lang_string()
  857%
  858%	Process a language string
  859
  860lang_string(String) -->
  861	"\"",
  862	string(Codes),
  863	"\"", !,
  864	{ atom_codes(Atom, Codes)
  865	},
  866	(   langsep
  867	->  language(Lang),
  868	    { String = literal(lang(Lang, Atom))
  869	    }
  870	;   "^^"
  871	->  uniref(Type),
  872	    { String = literal(type(Type, Atom))
  873	    }
  874	;   { String = literal(Atom)
  875	    }
  876	).
  877
  878langsep -->
  879	"-".
  880langsep -->
  881	"@".
  882
  883%	xml_string(String)
  884%
  885%	Handle xml"..."
  886
  887xml_string(xml(String)) -->
  888	"xml\"",			% really no whitespace?
  889	string(Codes),
  890	"\"",
  891	{ atom_codes(String, Codes)
  892	}.
  893
  894string([]) -->
  895	[].
  896string([C0|T]) -->
  897	string_char(C0),
  898	string(T).
  899
  900string_char(0'\\) -->
  901	"\\\\".
  902string_char(0'") -->
  903	"\\\"".
  904string_char(10) -->
  905	"\\n".
  906string_char(13) -->
  907	"\\r".
  908string_char(9) -->
  909	"\\t".
  910string_char(C) -->
  911	"\\u",
  912	'4xdigits'(C).
  913string_char(C) -->
  914	"\\U",
  915	'4xdigits'(C0),
  916	'4xdigits'(C1),
  917	{ C is C0<<16 + C1
  918	}.
  919string_char(C) -->
  920	[C].
  921
  922'4xdigits'(C) -->
  923	[C0,C1,C2,C3],
  924	{ code_type(C0, xdigit(V0)),
  925	  code_type(C1, xdigit(V1)),
  926	  code_type(C2, xdigit(V2)),
  927	  code_type(C3, xdigit(V3)),
  928
  929	  C is V0<<12 + V1<<8 + V2<<4 + V3
  930	}.
  931
  932%	language(-Lang)
  933%
  934%	Return xml:lang language identifier.
  935
  936language(Lang) -->
  937	lang_code(C0),
  938	lang_codes(Codes),
  939	{ atom_codes(Lang, [C0|Codes])
  940	}.
  941
  942lang_code(C) -->
  943	[C],
  944	{ C \== 0'.,
  945	  \+ code_type(C, white)
  946	}.
  947
  948lang_codes([C|T]) -->
  949	lang_code(C), !,
  950	lang_codes(T).
  951lang_codes([]) -->
  952	[].
 add_prefix(+Request)
Register a new prefix
  959add_prefix(Request) :-
  960	http_parameters(Request,
  961			[ prefix(Prefix),
  962			  uri(URI),
  963			  repository(Repository),
  964			  resultFormat(ResultFormat)
  965			],
  966			[ attribute_declarations(attribute_decl)
  967			]),
  968	authorized_api(write(Repository, add_prefix), ResultFormat),
  969	check_prefix(Prefix),
  970	api_action(Request,
  971		   rdf_register_prefix(Prefix, URI),
  972		   ResultFormat,
  973		   'Register prefix ~w --> ~w'-[Prefix, URI]).
  974
  975check_prefix(Prefix) :-
  976	xml_name(Prefix), !.
  977check_prefix(Prefix) :-
  978	domain_error(xml_name, Prefix).
  979
  980
  981		 /*******************************
  982		 *	 HTTP ATTRIBUTES	*
  983		 *******************************/
 attribute_decl(+OptionName, -Options)
Default options for specified attribute names. See http_parameters/3.
  990attribute_decl(repository,
  991	       [ optional(true),
  992		 description('Name of the repository (ignored)')
  993	       ]).
  994attribute_decl(query,
  995	       [ description('SPARQL or SeRQL quer-text')
  996	       ]).
  997attribute_decl(queryLanguage,
  998	       [ default('SPARQL'),
  999		 oneof(['SeRQL', 'SPARQL']),
 1000		 description('Query language used in query-text')
 1001	       ]).
 1002attribute_decl(serialization,
 1003	       [ default(rdfxml),
 1004		 oneof([ rdfxml,
 1005			 ntriples,
 1006			 n3
 1007		       ]),
 1008		 description('Serialization for graph-data')
 1009	       ]).
 1010attribute_decl(resultFormat,
 1011	       [ optional(true),
 1012		 oneof([ xml,
 1013			 html,
 1014			 rdf,
 1015			 json,
 1016			 csv
 1017		       ]),
 1018		 description('Serialization format of the result')
 1019	       ]).
 1020attribute_decl(resourceFormat,
 1021	       [ default(ns),
 1022		 oneof([ plain,
 1023			 ns,
 1024			 nslabel
 1025		       ]),
 1026		 description('How to format URIs in the table')
 1027	       ]).
 1028attribute_decl(entailment,		% cache?
 1029	       [ default(Default),
 1030		 oneof(Es),
 1031		 description('Reasoning performed')
 1032	       ]) :-
 1033	setting(cliopatria:default_entailment, Default),
 1034	findall(E, cliopatria:entailment(E, _), Es).
 1035attribute_decl(dataFormat,
 1036	       [ optional(true),
 1037		 oneof([rdfxml, ntriples, turtle]),
 1038		 description('Serialization of the data')
 1039	       ]).
 1040attribute_decl(baseURI,
 1041	       [ default('http://example.org/'),
 1042		 description('Base URI for relative resources')
 1043	       ]).
 1044attribute_decl(source,
 1045	       [ description('Name of the graph')
 1046	       ]).
 1047attribute_decl(verifyData,
 1048	       [ description('Verify the data (ignored)')
 1049	       | Options
 1050	       ]) :-
 1051	bool(off, Options).
 1052attribute_decl(schema,
 1053	       [ description('Include schema RDF in downloaded graph')
 1054	       | Options
 1055	       ]) :-
 1056	bool(off, Options).
 1057attribute_decl(data,
 1058	       [ description('Include non-schema RDF in downloaded graph')
 1059	       | Options
 1060	       ]) :-
 1061	bool(off, Options).
 1062attribute_decl(explicitOnly,
 1063	       [ description('Do not include entailed triples')
 1064	       | Options
 1065	       ]) :-
 1066	bool(off, Options).
 1067attribute_decl(niceOutput,
 1068	       [ description('Produce human-readable output (ignored; we always do that)')
 1069	       | Options
 1070	       ]) :-
 1071	bool(off, Options).
 1072attribute_decl(user,
 1073	       [ description('User name')
 1074	       ]).
 1075attribute_decl(password,
 1076	       [ description('Clear-text password')
 1077	       ]).
 1078
 1079					% Our extensions
 1080attribute_decl(storeAs,
 1081	       [ default(''),
 1082		 description('Store query under this name')
 1083	       ]).
 1084attribute_decl(persistent,
 1085	       [ description('Modify persistency of a graph'),
 1086		 oneof([on, off])
 1087	       ]).
 1088attribute_decl(uri,
 1089	       [ description('URI')
 1090	       ]).
 1091attribute_decl(prefix,
 1092	       [ description('Prefix (abbreviation)')
 1093	       ]).
 1094
 1095bool(Def,
 1096     [ default(Def),
 1097       oneof([on, off])
 1098     ]).
 result_format(+Request, ?Format) is det
 1103result_format(_Request, Format) :-
 1104	atom(Format), !.
 1105result_format(Request, _Format) :-
 1106	memberchk(accept(Accept), Request),
 1107	debug(sparql(result), 'Got accept = ~q', [Accept]),
 1108	fail.
 1109result_format(_Request, xml).
 1110
 1111
 1112accept_output_format(Request, Format) :-
 1113	memberchk(accept(Accept), Request),
 1114	(   atom(Accept)
 1115	->  http_parse_header_value(accept, Accept, Media)
 1116	;   Media = Accept
 1117	),
 1118	find_media(Media, Format), !.
 1119accept_output_format(_, xml).
 1120
 1121find_media([media(Type, _, _, _)|T], Format) :-
 1122	(   sparql_media(Type, Format)
 1123	->  true
 1124	;   find_media(T, Format)
 1125	).
 1126
 1127sparql_media(application/'sparql-results+xml',   xml).
 1128sparql_media(application/'sparql-results+json', json).
 api_action(+Request, :Goal, +Format, +Message)
Perform some -modifying- goal, reporting time, triples and subject statistics.
Arguments:
Format- specifies the result format and is one of html, xml or rdf.
Message- is passed to html_write//1.
 1139api_action(Request, G, html, Message) :- !,
 1140	call_showing_messages(
 1141	    api_action2(Request, G, html, Message),
 1142	    [ header(h4(Message)),
 1143	      footer([])
 1144	    ]).
 1145api_action(Request, G, Format, Message) :-
 1146	api_action2(Request, G, Format, Message).
 1147
 1148api_action2(_Request, G, Format, Message) :-
 1149	logged_on(User, anonymous),
 1150	get_time(T0), T is integer(T0),
 1151	statistics(cputime, CPU0),
 1152	rdf_statistics(triples(Triples0)),
 1153	subjects(Subjects0),
 1154	run(G, sesame(User, T)),
 1155	subjects(Subjects1),
 1156	rdf_statistics(triples(Triples1)),
 1157	statistics(cputime, CPU1),
 1158	CPU is CPU1 - CPU0,
 1159	Triples is Triples1 - Triples0,
 1160	Subjects is Subjects1 - Subjects0,
 1161	done(Format, Message, CPU, Subjects, Triples).
 1162
 1163:- if(rdf_statistics(subjects(_))).	% RDF 2.x
 1164subjects(Count) :- rdf_statistics(subjects(Count)).
 1165subj_label --> html('Subjects').
 1166:- else.				% RDF 3.0
 1167subjects(Count) :- rdf_statistics(resources(Count)).
 1168subj_label --> html('Resources').
 1169:- endif. 1170
 1171:- meta_predicate
 1172	run(0, +). 1173
 1174run(M:(A,B), Log) :- !,
 1175	run(M:A, Log),
 1176	run(M:B, Log).
 1177run(Goal, _) :-
 1178	no_transaction(Goal), !,
 1179	call(Goal).
 1180run(A, Log) :-
 1181	rdf_transaction(A, Log).
 1182
 1183no_transaction(_:rdf_reset_db).
 1184no_transaction(_:rdf_unload_graph(_)).
 1185no_transaction(_:rdf_flush_journals(_)).
 1186no_transaction(cpa_browse:multigraph_action(_,_)).
 1187
 1188done(html, _Message, CPU, Subjects, Triples) :-
 1189	after_messages([ \result_table(CPU, Subjects, Triples)
 1190		       ]).
 1191done(Format, _:Message, CPU, Subjects, Triples) :- !,
 1192	done(Format, Message, CPU, Subjects, Triples).
 1193done(json, Fmt-Args, _CPU, _Subjects, _Triples) :-
 1194	format(string(Message), Fmt, Args),
 1195	format('Content-type: application/json~n~n'),
 1196	json_write(current_output,
 1197		json([transaction=
 1198			 json([status=
 1199				  json([msg=Message])])])),
 1200	format('~n').
 1201done(xml, Fmt-Args, _CPU, _Subjects, _Triples) :-
 1202	format(string(Message), Fmt, Args),
 1203	format('Content-type: text/xml~n~n'),
 1204	format('<transaction>~n'),
 1205	format('  <status>~n'),
 1206	format('     <msg>~w</msg>~n', [Message]),
 1207	format('  </status>~n'),
 1208	format('</transaction>~n').
 1209done(Format, Fmt-Args, _CPU, _Subjects, _Triples) :-
 1210	format('Content-type: text/plain~n~n'),
 1211	format('resultFormat=~w not yet supported~n~n', Format),
 1212	format(Fmt, Args).
 result_table(+CPU, +SubDiff, +TripleDiff)// is det
HTML component that summarises the result of an operation.
 1219result_table(CPU, Subjects, Triples) -->
 1220	{ rdf_statistics(triples(TriplesNow)),
 1221	  subjects(SubjectsNow)
 1222	},
 1223	html([ h4('Operation completed'),
 1224	       table([ id('result'),
 1225		       class(block)
 1226		     ],
 1227		     [ tr([td(class(empty), ''), th('+/-'), th('now')]),
 1228		       tr([th(class(p_name), 'CPU time'),
 1229			   \nc('~3f', CPU), td('')]),
 1230		       tr([th(class(p_name), \subj_label),
 1231			   \nc('~D', Subjects), \nc('~D', SubjectsNow)]),
 1232		       tr([th(class(p_name), 'Triples'),
 1233			   \nc('~D', Triples), \nc('~D', TriplesNow)])
 1234		     ])
 1235	     ]).
 authorized_api(+Action, +ResultFormat) is det
Errors
- permission_error(http_location, access, Path)
 1242authorized_api(Action, ResultFormat) :-
 1243	ResultFormat == html, !,	% do not bind
 1244	authorized(Action).
 1245authorized_api(Action, _) :-
 1246	logged_on(User, anonymous),
 1247	check_permission(User, Action)