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_sesame,
   37          [ api_action/4                % +Request, +Goal, +Format, +Message
   38          ]).   39:- use_module(rdfql(serql)).   40:- use_module(rdfql(sparql)).   41:- use_module(rdfql(rdf_io)).   42:- use_module(rdfql(rdf_html)).   43:- use_module(library(http/http_parameters)).   44:- use_module(user(user_db)).   45:- use_module(library(semweb/rdfs)).   46:- use_module(library(semweb/rdf_db)).   47:- use_module(library(semweb/rdf_http_plugin)).   48:- use_module(library(semweb/rdf_file_type)).   49:- use_module(library(semweb/rdf_persistency)).   50:- use_module(library(http/html_write)).   51:- use_module(library(http/http_request_value)).   52:- use_module(library(http/http_dispatch)).   53:- use_module(library(http/http_client)).   54:- use_module(library(http/http_open)).   55:- use_module(library(http/json)).   56:- use_module(library(memfile)).   57:- use_module(library(debug)).   58:- use_module(library(lists)).   59:- use_module(library(option)).   60:- use_module(library(apply)).   61:- use_module(library(settings)).   62:- use_module(components(query)).   63:- use_module(components(basics)).   64:- use_module(components(messages)).   65
   66:- meta_predicate(api_action2(+,0,+,+)).   67
   68:- http_handler(sesame('login'),              http_login,           []).   69:- http_handler(sesame('logout'),             http_logout,          []).   70:- http_handler(sesame('evaluateQuery'),      evaluate_query,
   71                [spawn(sparql_query)]).   72:- http_handler(sesame('evaluateGraphQuery'), evaluate_graph_query,
   73                [spawn(sparql_query)]).   74:- http_handler(sesame('evaluateTableQuery'), evaluate_table_query,
   75                [spawn(sparql_query)]).   76:- http_handler(sesame('extractRDF'),         extract_rdf,          []).   77:- http_handler(sesame('listRepositories'),   list_repositories,    []).   78:- http_handler(sesame('clearRepository'),    clear_repository,     []).   79:- http_handler(sesame('unloadSource'),       unload_source,
   80                [ time_limit(infinite) ]).   81:- http_handler(sesame('unloadGraph'),        unload_graph,
   82                [ time_limit(infinite) ]).   83:- http_handler(sesame('uploadData'),         upload_data,
   84                [ time_limit(infinite) ]).   85:- http_handler(sesame('uploadURL'),          upload_url,
   86                [ time_limit(infinite) ]).   87:- http_handler(sesame('removeStatements'),   remove_statements,
   88                [ time_limit(infinite) ]).   89:- http_handler(sesame('flushJournal'),       flush_journal,
   90                [ time_limit(infinite) ]).   91:- http_handler(sesame('modifyPersistency'),  modify_persistency,
   92                [ time_limit(infinite) ]).   93:- http_handler(sesame('addPrefix'),          add_prefix, []).   94:- http_handler(sesame('defPrefix'),          del_prefix, []).   95
   96:- html_meta
   97    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.
  110http_login(Request) :-
  111    http_parameters(Request,
  112                    [ user(User),
  113                      password(Password),
  114                      resultFormat(ResultFormat)
  115                    ],
  116                    [ attribute_declarations(attribute_decl)
  117                    ]),
  118    result_format(Request, ResultFormat),
  119    api_action(Request,
  120               (   validate_login(Request, User, Password),
  121                   login(User)
  122               ),
  123               ResultFormat,
  124               'Login ~w'-[User]).
  125
  126validate_login(_, User, Password) :-
  127    validate_password(User, Password),
  128    !.
  129validate_login(Request, _, _) :-
  130    memberchk(path(Path), Request),
  131    throw(http_reply(forbidden(Path))).
 http_logout(+Request)
HTTP handler to logout current user.
  138http_logout(Request) :-
  139    http_parameters(Request,
  140                    [ resultFormat(ResultFormat)
  141                    ],
  142                    [ attribute_declarations(attribute_decl)
  143                    ]),
  144    result_format(Request, ResultFormat),
  145    api_action(Request,
  146               logout_user(Message),
  147               ResultFormat,
  148               Message).
  149
  150logout_user('Logout ~w'-[User]) :-
  151    logged_on(User),
  152    !,
  153    logout(User).
  154logout_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.
  164evaluate_query(Request) :-
  165    http_parameters(Request,
  166                    [ repository(Repository),
  167                      query(Query),
  168                      queryLanguage(QueryLanguage),
  169                      resultFormat(ResultFormat),
  170                      serialization(Serialization),
  171                      resourceFormat(ResourceFormat),
  172                      entailment(Entailment),
  173                      storeAs(SaveAs)
  174                    ],
  175                    [ attribute_declarations(attribute_decl)
  176                    ]),
  177    result_format(Request, ResultFormat),
  178    statistics(cputime, CPU0),
  179    downcase_atom(QueryLanguage, QLang),
  180    compile(QLang, Query, Compiled,
  181            [ entailment(Entailment),
  182              type(Type)
  183            ]),
  184    authorized_query(Type, Repository, ResultFormat),
  185    findall(Reply, run(QLang, Compiled, Reply), Result),
  186    statistics(cputime, CPU1),
  187    CPU is CPU1 - CPU0,
  188    store_query(construct, SaveAs, Query),
  189    (   graph_type(Type)
  190    ->  write_graph(Result,
  191                    [ result_format(ResultFormat),
  192                      serialization(Serialization),
  193                      resource_format(ResourceFormat),
  194                      cputime(CPU)
  195                    ])
  196    ;   Type = select(VarNames)
  197    ->  write_table(Result,
  198                    [ variables(VarNames),
  199                      result_format(ResultFormat),
  200                      serialization(Serialization),
  201                      resource_format(ResourceFormat),
  202                      cputime(CPU)
  203                    ])
  204    ;   Type == ask, Result = [Reply]
  205    ->  reply_html_page(cliopatria(default),
  206                        title('ASK Result'),
  207                        [ h4('ASK query completed'),
  208                          p(['Answer = ', Reply])
  209                        ])
  210    ;   Type == update, Result = [Reply]
  211    ->  reply_html_page(cliopatria(default),
  212                        title('Update Result'),
  213                        [ h4('Update query completed'),
  214                          p(['Answer = ', Reply])
  215                        ])
  216    ).
  217
  218
  219authorized_query(update, Repository, ResultFormat) :-
  220    !,
  221    authorized_api(write(Repository, sparql(update)), ResultFormat).
  222authorized_query(_, Repository, ResultFormat) :-
  223    authorized_api(read(Repository, query), ResultFormat).
 evaluate_graph_query(+Request)
Handle CONSTRUCT queries.
  229evaluate_graph_query(Request) :-
  230    http_parameters(Request,
  231                    [ repository(Repository),
  232                      query(Query),
  233                      queryLanguage(QueryLanguage),
  234                      resultFormat(ResultFormat),
  235                      serialization(Serialization),
  236                      resourceFormat(ResourceFormat),
  237                      entailment(Entailment),
  238                      storeAs(SaveAs)
  239                    ],
  240                    [ attribute_declarations(attribute_decl)
  241                    ]),
  242    result_format(Request, ResultFormat),
  243    authorized_api(read(Repository, query), ResultFormat),
  244    statistics(cputime, CPU0),
  245    downcase_atom(QueryLanguage, QLang),
  246    compile(QLang, Query, Compiled,
  247            [ entailment(Entailment),
  248              type(Type)
  249            ]),
  250    (   graph_type(Type)
  251    ->  true
  252    ;   throw(error(domain_error(query_type(graph), Type), _))
  253    ),
  254    findall(T, run(QLang, Compiled, T), Triples),
  255    statistics(cputime, CPU1),
  256    store_query(construct, SaveAs, Query),
  257    CPU is CPU1 - CPU0,
  258    write_graph(Triples,
  259                [ result_format(ResultFormat),
  260                  serialization(Serialization),
  261                  resource_format(ResourceFormat),
  262                  cputime(CPU)
  263                ]).
  264
  265graph_type(construct).
  266graph_type(describe).
 evaluate_table_query(+Request)
Handle SELECT queries.
  272evaluate_table_query(Request) :-
  273    http_parameters(Request,
  274                    [ repository(Repository),
  275                      query(Query),
  276                      queryLanguage(QueryLanguage),
  277                      resultFormat(ResultFormat),
  278                      serialization(Serialization),
  279                      resourceFormat(ResourceFormat),
  280                      entailment(Entailment),
  281                      storeAs(SaveAs)
  282                    ],
  283                    [ attribute_declarations(attribute_decl)
  284                    ]),
  285    result_format(Request, ResultFormat),
  286    authorized_api(read(Repository, query), ResultFormat),
  287    statistics(cputime, CPU0),
  288    downcase_atom(QueryLanguage, QLang),
  289    compile(QLang, Query, Compiled,
  290            [ entailment(Entailment),
  291              type(select(VarNames))
  292            ]),
  293    findall(R, run(QLang, Compiled, R), Rows),
  294    statistics(cputime, CPU1),
  295    CPU is CPU1 - CPU0,
  296    store_query(select, SaveAs, Query),
  297    write_table(Rows,
  298                [ variables(VarNames),
  299                  result_format(ResultFormat),
  300                  serialization(Serialization),
  301                  resource_format(ResourceFormat),
  302                  cputime(CPU)
  303                ]).
 compile(+Language, +Query, -Compiled, +Options)
Compile a query and validate the query-type
  309compile(serql, Query, Compiled, Options) :-
  310    !,
  311    serql_compile(Query, Compiled, Options).
  312compile(sparql, Query, Compiled, Options) :-
  313    !,
  314    sparql_compile(Query, Compiled, Options).
  315compile(Language, _, _, _) :-
  316    throw(error(domain_error(query_language, Language), _)).
 run(+Language, +Compiled, -Reply)
  320run(serql, Compiled, Reply) :-
  321    serql_run(Compiled, Reply).
  322run(sparql, Compiled, Reply) :-
  323    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.
  333extract_rdf(Request) :-
  334    http_parameters(Request,
  335                    [ repository(Repository),
  336                      schema(Schema),
  337                      data(Data),
  338                      explicitOnly(ExplicitOnly),
  339                      niceOutput(_NiceOutput),
  340                      serialization(Serialization)
  341                    ],
  342                    [ attribute_declarations(attribute_decl)
  343                    ]),
  344    authorized(read(Repository, download)),
  345    statistics(cputime, CPU0),
  346    findall(T, export_triple(Schema, Data, ExplicitOnly, T), Triples),
  347    statistics(cputime, CPU1),
  348    CPU is CPU1 - CPU0,
  349    write_graph(Triples,
  350                [ serialization(Serialization),
  351                  cputime(CPU)
  352                ]).
 export_triple(+Schema, +Data, +ExplicitOnly, -RDF)
  357export_triple(off, off, _, _) :-
  358    !,
  359    fail.                           % no data requested
  360export_triple(on, on, on, rdf(S,P,O)) :-
  361    !,
  362    rdf_db:rdf(S,P,O).
  363export_triple(on, on, off, rdf(S,P,O)) :-
  364    !,
  365    rdfs_entailment:rdf(S,P,O).
  366export_triple(off, on, Explicit, RDF) :-
  367    export_triple(on, on, Explicit, RDF),
  368    \+ schema_triple(RDF).
  369export_triple(on, off, Explicit, RDF) :-
  370    export_triple(on, on, Explicit, RDF),
  371    schema_triple(RDF).
  372
  373schema_triple(rdf(S,_P,_O)) :-
  374    rdfs_individual_of(S, rdf:'Property').
  375schema_triple(rdf(S,_P,_O)) :-
  376    rdfs_individual_of(S, rdfs:'Class').
 list_repositories(+Request)
List the available repositories. This is only default for now
  383list_repositories(_Request) :-
  384    Repository = default,
  385    logged_on(User, anonymous),
  386    (   catch(check_permission(User, write(Repository, _)), _, fail)
  387    ->  Write = true
  388    ;   Write = false
  389    ),
  390    (   catch(check_permission(User, read(Repository, _)), _, fail)
  391    ->  Read = true
  392    ;   Read = false
  393    ),
  394    format('Content-type: text/xml~n~n'),
  395    format('<?xml version="1.0" encoding="ISO-8859-1"?>~n~n', []),
  396    format('<repositorylist>~n'),
  397    format('  <repository id="default" readable="~w" writeable="~w">~n',
  398           [ Read, Write ]),
  399    format('    <title>Default repository</title>~n'),
  400    format('  </repository>~n'),
  401    format('</repositorylist>~n').
 clear_repository(+Request)
Clear the repository.
  408clear_repository(Request) :-
  409    http_parameters(Request,
  410                    [ repository(Repository),
  411                      resultFormat(ResultFormat)
  412                    ],
  413                    [ attribute_declarations(attribute_decl)
  414                    ]),
  415    result_format(Request, ResultFormat),
  416    authorized_api(write(Repository, clear), ResultFormat),
  417    api_action(Request,
  418               rdf_reset_db,
  419               ResultFormat,
  420               'Clear database'-[]).
 unload_source(+Request)
Remove triples loaded from a specified source
  426unload_source(Request) :-
  427    http_parameters(Request,
  428                    [ repository(Repository),
  429                      source(Source),
  430                      resultFormat(ResultFormat)
  431                    ],
  432                    [ attribute_declarations(attribute_decl)
  433                    ]),
  434    result_format(Request, ResultFormat),
  435    authorized_api(write(Repository, unload(Source)), ResultFormat),
  436    api_action(Request, rdf_unload(Source),
  437               ResultFormat,
  438               'Unload triples from ~w'-[Source]).
 unload_graph(+Request)
Remove a named graph.
  445unload_graph(Request) :-
  446    http_parameters(Request,
  447                    [ repository(Repository),
  448                      graph(Graph, []),
  449                      resultFormat(ResultFormat)
  450                    ],
  451                    [ attribute_declarations(attribute_decl)
  452                    ]),
  453    result_format(Request, ResultFormat),
  454    authorized_api(write(Repository, unload(Graph)), ResultFormat),
  455    api_action(Request, rdf_unload_graph(Graph),
  456               ResultFormat,
  457               'Unload triples from ~w'-[Graph]).
 flush_journal(+Request)
Flush the journal of the requested graph
  464flush_journal(Request) :-
  465    http_parameters(Request,
  466                    [ repository(Repository),
  467                      graph(Graph, []),
  468                      resultFormat(ResultFormat)
  469                    ],
  470                    [ attribute_declarations(attribute_decl)
  471                    ]),
  472    result_format(Request, ResultFormat),
  473    authorized_api(write(Repository, unload(Graph)), ResultFormat),
  474    api_action(Request, rdf_flush_journals([graph(Graph)]),
  475               ResultFormat,
  476               'Flushed journals for graph ~w'-[Graph]).
 modify_persistency(+Request)
Change the persistent properties for the requested graph
  483modify_persistency(Request) :-
  484    http_parameters(Request,
  485                    [ repository(Repository),
  486                      graph(Graph, []),
  487                      resultFormat(ResultFormat),
  488                      persistent(Persistent)
  489                    ],
  490                    [ attribute_declarations(attribute_decl)
  491                    ]),
  492    persistency(Persistent, PVal, Action),
  493    result_format(Request, ResultFormat),
  494    authorized_api(write(Repository, persistent(Graph)), ResultFormat),
  495    api_action(Request, rdf_persistency(Graph, PVal),
  496               ResultFormat,
  497               '~w persistency for graph ~w'-[Action, Graph]).
  498
  499persistency(on,  true,  'Set').
  500persistency(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.
  512:- 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).
  524:- public create_tmp_file/3.  525create_tmp_file(Stream, file(File, Options), Options) :-
  526    setup_call_catcher_cleanup(
  527        tmp_file_stream(binary, File, Out),
  528        copy_stream_data(Stream, Out),
  529        Why,
  530        cleanup(Why, File, Out)).
  531
  532cleanup(Why, File, Out) :-
  533    close(Out),
  534    (   Why == exit
  535    ->  true
  536    ;   catch(delete_file(File), _, true)
  537    ).
 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).
  545upload_data_file(Request, Data, TmpFile, FileOptions) :-
  546    http_convert_parameters(Data,
  547                            [ repository(Repository),
  548                              dataFormat(DataFormat),
  549                              baseURI(BaseURI),
  550                              verifyData(_Verify),
  551                              resultFormat(ResultFormat)
  552                            ],
  553                            attribute_decl),
  554    result_format(Request, ResultFormat),
  555    authorized_api(write(Repository, load(posted)), ResultFormat),
  556    phrase(load_option(DataFormat, BaseURI), LoadOptions),
  557    append(LoadOptions, FileOptions, Options),
  558    api_action(Request,
  559               setup_call_cleanup(
  560                   open(TmpFile, read, Stream),
  561                   rdf_guess_format_and_load(Stream, Options),
  562                   close(Stream)),
  563               ResultFormat,
  564               'Load data from POST'-[]).
  565
  566upload_option(_=_) :- !.
  567upload_option(Term) :- functor(Term, _, 1).
  568
  569upload_data(Request) :-
  570    option(method(post), Request),
  571    !,
  572    http_read_data(Request, Data,
  573                   [ on_filename(create_tmp_file)
  574                   ]),
  575    (   option(data(file(TmpFile, FileOptions)), Data)
  576    ->  true
  577    ;   existence_error(attribute_declaration, data)
  578    ),
  579    include(upload_option, FileOptions, Options),
  580    call_cleanup(upload_data_file(Request, Data, TmpFile, Options),
  581                 catch(delete_file(TmpFile), _, true)).
  582
  583:- endif.  584upload_data(Request) :-
  585    http_parameters(Request,
  586                    [ repository(Repository),
  587                      data(Data,
  588                           [ description('RDF data to be loaded')
  589                           ]),
  590                      dataFormat(DataFormat),
  591                      baseURI(BaseURI),
  592                      verifyData(_Verify),
  593                      resultFormat(ResultFormat)
  594                    ],
  595                    [ attribute_declarations(attribute_decl)
  596                    ]),
  597    result_format(Request, ResultFormat),
  598    authorized_api(write(Repository, load(posted)), ResultFormat),
  599    phrase(load_option(DataFormat, BaseURI), Options),
  600    atom_to_memory_file(Data, MemFile),
  601    api_action(Request,
  602               setup_call_cleanup(open_memory_file(MemFile, read, Stream),
  603                                  rdf_guess_format_and_load(Stream, Options),
  604                                  ( close(Stream),
  605                                    free_memory_file(MemFile)
  606                                  )),
  607               ResultFormat,
  608               '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
  621upload_url(Request) :-
  622    http_parameters(Request,
  623                    [ url(URL, []),
  624                      dataFormat(DataFormat),
  625                      baseURI(BaseURI,
  626                              [ default(URL)
  627                              ]),
  628                      resultFormat(ResultFormat),
  629                      verifyData(_Verify),
  630                      repository(Repository)
  631                    ],
  632                    [ attribute_declarations(attribute_decl)
  633                    ]),
  634    result_format(Request, ResultFormat),
  635    authorized_api(write(Repository, load(url(URL))), ResultFormat),
  636    phrase(load_option(DataFormat, BaseURI), Options),
  637    api_action(Request,
  638               load_from_url(URL, Options),
  639               ResultFormat,
  640               'Load data from ~w'-[URL]).
  641
  642load_from_url(URL, Options) :-
  643    http_open(URL, In,
  644              [ cert_verify_hook(ssl_verify)
  645              ]),
  646    call_cleanup(rdf_guess_format_and_load(In, Options),
  647                 close(In)).
  648
  649:- 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.
  657ssl_verify(_SSL,
  658           _ProblemCertificate, _AllCertificates, _FirstCertificate,
  659           _Error).
  660
  661load_option(DataFormat, BaseURI) -->
  662    data_format_option(DataFormat),
  663    base_uri_option(BaseURI).
  664
  665data_format_option(Var)      --> {var(Var)}, !.
  666data_format_option(rdfxml)   --> [format(xml)].
  667data_format_option(ntriples) --> [format(turtle)].
  668data_format_option(turtle)   --> [format(turtle)].
  669
  670base_uri_option(Var) --> {var(Var)}, !.
  671base_uri_option(URI) --> [base_uri(URI)].
 remove_statements(+Request)
Remove statements from the database
  678remove_statements(Request) :-
  679    http_parameters(Request,
  680                    [ repository(Repository, [optional(true)]),
  681                      resultFormat(ResultFormat),
  682                                    % as documented
  683                      subject(Subject, [optional(true)]),
  684                      predicate(Predicate, [optional(true)]),
  685                      object(Object, [optional(true)]),
  686                                    % remove (turtle) graph
  687                      baseURI(BaseURI),
  688                      dataFormat(DataFormat),
  689                      data(Data, [optional(true)])
  690                    ],
  691                    [ attribute_declarations(attribute_decl)
  692                    ]),
  693    result_format(Request, ResultFormat),
  694    instantiated(Subject, SI),
  695    instantiated(Predicate, PI),
  696    instantiated(Object, OI),
  697    authorized_api(write(Repository, remove_statements(SI, PI, OI)),
  698                   ResultFormat),
  699
  700    (   nonvar(Data)
  701    ->  setup_call_cleanup(( atom_to_memory_file(Data, MemFile),
  702                             open_memory_file(MemFile, read, Stream,
  703                                              [ free_on_close(true)
  704                                              ])
  705                           ),
  706                           ( rdf_guess_data_format(Stream, DataFormat),
  707                             get_triples(stream(Stream),
  708                                         Triples,
  709                                         [ base_uri(BaseURI),
  710                                           data_format(DataFormat)
  711                                         ])
  712                           ),
  713                           close(Stream)),
  714        length(Triples, NTriples),
  715        debug(removeStatements, 'Removing ~D statements', [NTriples]),
  716        api_action(Request,
  717                   remove_triples(Triples),
  718                   ResultFormat,
  719                   'Remove ~D triples'-[NTriples])
  720    ;   debug(removeStatements, 'removeStatements = ~w',
  721              [rdf(Subject, Predicate, Object)]),
  722
  723        ntriple_part(Subject,   subject,   S),
  724        ntriple_part(Predicate, predicate, P),
  725        ntriple_part(Object,    object,    O),
  726
  727        debug(removeStatements, 'Action = ~q', [rdf_retractall(S,P,O)]),
  728        api_action(Request,
  729                   rdf_retractall(S,P,O),
  730                   ResultFormat,
  731                   'Remove statements from ~k'-[rdf(S,P,O)])
  732    ).
 remove_triples(+List)
Remove indicated triples from the database.
  738remove_triples([]).
  739remove_triples([rdf(S,P,O)|T]) :-
  740    rdf_retractall(S,P,O),
  741    remove_triples(T).
  742
  743instantiated(X, I) :-
  744    (   var(X)
  745    ->  I = (-)
  746    ;   I = (+)
  747    ).
  748
  749ntriple_part(In, _, _) :-
  750    var(In),
  751    !.
  752ntriple_part('', _, _) :- !.
  753ntriple_part(In, Field, Out) :-
  754    atom_codes(In, Codes),
  755    phrase(rdf_ntriple_part(Field, Out), Codes),
  756    !.
  757ntriple_part(Text, Field, _) :-
  758    throw(error(type_error(ntriples(Field), Text),
  759                context(_,
  760                        '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.
  770rdf_ntriple_part(subject, Subject) -->
  771    subject(Subject).
  772rdf_ntriple_part(predicate, Predicate) -->
  773    predicate(Predicate).
  774rdf_ntriple_part(object, Object) -->
  775    object(Object).
  776
  777subject(Subject) -->
  778    uniref(Subject),
  779    !.
  780subject(Subject) -->
  781    node_id(Subject).
  782
  783predicate(Predicate) -->
  784    uniref(Predicate).
  785
  786object(Object) -->
  787    uniref(Object),
  788    !.
  789object(Object) -->
  790    node_id(Object).
  791object(Object) -->
  792    literal(Object).
  793
  794
  795uniref(URI) -->
  796    "<",
  797    escaped_uri_codes(Codes),
  798    ">",
  799    !,
  800    { atom_codes(URI, Codes)
  801    }.
  802
  803node_id(node(Id)) -->                   % anonymous nodes
  804    "_:",
  805    name_start(C0),
  806    name_codes(Codes),
  807    { atom_codes(Id, [C0|Codes])
  808    }.
  809
  810literal(Literal) -->
  811    lang_string(Literal),
  812    !.
  813literal(Literal) -->
  814    xml_string(Literal).
  815
  816
  817%       name_start(-Code)
  818%       name_codes(-ListfCodes)
  819%
  820%       Parse identifier names
  821
  822name_start(C) -->
  823    [C],
  824    { code_type(C, alpha)
  825    }.
  826
  827name_codes([C|T]) -->
  828    [C],
  829    { code_type(C, alnum)
  830    },
  831    !,
  832    name_codes(T).
  833name_codes([]) -->
  834    [].
  835
  836
  837%       escaped_uri_codes(-CodeList)
  838%
  839%       Decode string holding %xx escaped characters.
  840
  841escaped_uri_codes([]) -->
  842    [].
  843escaped_uri_codes([C|T]) -->
  844    "%", [D0,D1],
  845    !,
  846    { code_type(D0, xdigit(V0)),
  847      code_type(D1, xdigit(V1)),
  848      C is V0<<4 + V1
  849    },
  850    escaped_uri_codes(T).
  851escaped_uri_codes([C|T]) -->
  852    "\\u", [D0,D1,D2,D3],
  853    !,
  854    { code_type(D0, xdigit(V0)),
  855      code_type(D1, xdigit(V1)),
  856      code_type(D2, xdigit(V2)),
  857      code_type(D3, xdigit(V3)),
  858      C is V0<<12 + V1<<8 + V2<<4 + V3
  859    },
  860    escaped_uri_codes(T).
  861escaped_uri_codes([C|T]) -->
  862    "\\U", [D0,D1,D2,D3,D4,D5,D6,D7],
  863    !,
  864    { code_type(D0, xdigit(V0)),
  865      code_type(D1, xdigit(V1)),
  866      code_type(D2, xdigit(V2)),
  867      code_type(D3, xdigit(V3)),
  868      code_type(D4, xdigit(V4)),
  869      code_type(D5, xdigit(V5)),
  870      code_type(D6, xdigit(V6)),
  871      code_type(D7, xdigit(V7)),
  872      C is V0<<28 + V1<<24 + V2<<20 + V3<<16 +
  873           V4<<12 + V5<<8 + V6<<4 + V7
  874    },
  875    escaped_uri_codes(T).
  876escaped_uri_codes([C|T]) -->
  877    [C],
  878    escaped_uri_codes(T).
  879
  880%       lang_string()
  881%
  882%       Process a language string
  883
  884lang_string(String) -->
  885    "\"",
  886    string(Codes),
  887    "\"",
  888    !,
  889    { atom_codes(Atom, Codes)
  890    },
  891    (   langsep
  892    ->  language(Lang),
  893        { String = literal(lang(Lang, Atom))
  894        }
  895    ;   "^^"
  896    ->  uniref(Type),
  897        { String = literal(type(Type, Atom))
  898        }
  899    ;   { String = literal(Atom)
  900        }
  901    ).
  902
  903langsep -->
  904    "-".
  905langsep -->
  906    "@".
  907
  908%       xml_string(String)
  909%
  910%       Handle xml"..."
  911
  912xml_string(xml(String)) -->
  913    "xml\"",                        % really no whitespace?
  914    string(Codes),
  915    "\"",
  916    { atom_codes(String, Codes)
  917    }.
  918
  919string([]) -->
  920    [].
  921string([C0|T]) -->
  922    string_char(C0),
  923    string(T).
  924
  925string_char(0'\\) -->
  926    "\\\\".
  927string_char(0'") -->
  928    "\\\"".
  929string_char(10) -->
  930    "\\n".
  931string_char(13) -->
  932    "\\r".
  933string_char(9) -->
  934    "\\t".
  935string_char(C) -->
  936    "\\u",
  937    '4xdigits'(C).
  938string_char(C) -->
  939    "\\U",
  940    '4xdigits'(C0),
  941    '4xdigits'(C1),
  942    { C is C0<<16 + C1
  943    }.
  944string_char(C) -->
  945    [C].
  946
  947'4xdigits'(C) -->
  948    [C0,C1,C2,C3],
  949    { code_type(C0, xdigit(V0)),
  950      code_type(C1, xdigit(V1)),
  951      code_type(C2, xdigit(V2)),
  952      code_type(C3, xdigit(V3)),
  953
  954      C is V0<<12 + V1<<8 + V2<<4 + V3
  955    }.
  956
  957%       language(-Lang)
  958%
  959%       Return xml:lang language identifier.
  960
  961language(Lang) -->
  962    lang_code(C0),
  963    lang_codes(Codes),
  964    { atom_codes(Lang, [C0|Codes])
  965    }.
  966
  967lang_code(C) -->
  968    [C],
  969    { C \== 0'.,
  970      \+ code_type(C, white)
  971    }.
  972
  973lang_codes([C|T]) -->
  974    lang_code(C),
  975    !,
  976    lang_codes(T).
  977lang_codes([]) -->
  978    [].
 add_prefix(+Request)
Register a new prefix
  985add_prefix(Request) :-
  986    http_parameters(Request,
  987                    [ prefix(Prefix),
  988                      uri(URI),
  989                      repository(Repository),
  990                      resultFormat(ResultFormat)
  991                    ],
  992                    [ attribute_declarations(attribute_decl)
  993                    ]),
  994    authorized_api(write(Repository, add_prefix), ResultFormat),
  995    check_prefix(Prefix),
  996    api_action(Request,
  997               rdf_register_prefix(Prefix, URI),
  998               ResultFormat,
  999               'Register prefix ~w --> ~w'-[Prefix, URI]).
 1000
 1001del_prefix(Request) :-
 1002    http_parameters(Request,
 1003                    [ prefix(Prefix),
 1004                      repository(Repository),
 1005                      resultFormat(ResultFormat)
 1006                    ],
 1007                    [ attribute_declarations(attribute_decl)
 1008                    ]),
 1009    authorized_api(write(Repository, del_prefix), ResultFormat),
 1010    (   rdf_current_prefix(Prefix, URI)
 1011    ->  api_action(Request,
 1012                   rdf_unregister_prefix(Prefix),
 1013                   ResultFormat,
 1014                   'Removed prefix ~w (was ~w)'-[Prefix, URI])
 1015    ;   api_action(Request,
 1016                   true,
 1017                   ResultFormat,
 1018                   'Prefix ~w was unknown'-[Prefix])
 1019    ).
 1020
 1021:- if(\+current_predicate(rdf_unregister_prefix/1)). 1022rdf_unregister_prefix(Prefix) :-
 1023    retractall(rdf_db:ns(Prefix, _)).
 1024:- endif. 1025
 1026check_prefix(Prefix) :-
 1027    xml_name(Prefix),
 1028    !.
 1029check_prefix(Prefix) :-
 1030    domain_error(xml_name, Prefix).
 1031
 1032
 1033                 /*******************************
 1034                 *       HTTP ATTRIBUTES        *
 1035                 *******************************/
 attribute_decl(+OptionName, -Options)
Default options for specified attribute names. See http_parameters/3.
 1042attribute_decl(repository,
 1043               [ optional(true),
 1044                 description('Name of the repository (ignored)')
 1045               ]).
 1046attribute_decl(query,
 1047               [ description('SPARQL or SeRQL quer-text')
 1048               ]).
 1049attribute_decl(queryLanguage,
 1050               [ default('SPARQL'),
 1051                 oneof(['SeRQL', 'SPARQL']),
 1052                 description('Query language used in query-text')
 1053               ]).
 1054attribute_decl(serialization,
 1055               [ default(rdfxml),
 1056                 oneof([ rdfxml,
 1057                         ntriples,
 1058                         n3
 1059                       ]),
 1060                 description('Serialization for graph-data')
 1061               ]).
 1062attribute_decl(resultFormat,
 1063               [ optional(true),
 1064                 oneof([ xml,
 1065                         html,
 1066                         rdf,
 1067                         json,
 1068                         csv
 1069                       ]),
 1070                 description('Serialization format of the result')
 1071               ]).
 1072attribute_decl(resourceFormat,
 1073               [ default(ns),
 1074                 oneof([ plain,
 1075                         ns,
 1076                         nslabel
 1077                       ]),
 1078                 description('How to format URIs in the table')
 1079               ]).
 1080attribute_decl(entailment,              % cache?
 1081               [ default(Default),
 1082                 oneof(Es),
 1083                 description('Reasoning performed')
 1084               ]) :-
 1085    setting(cliopatria:default_entailment, Default),
 1086    findall(E, cliopatria:entailment(E, _), Es).
 1087attribute_decl(dataFormat,
 1088               [ optional(true),
 1089                 oneof([rdfxml, ntriples, turtle]),
 1090                 description('Serialization of the data')
 1091               ]).
 1092attribute_decl(baseURI,
 1093               [ default('http://example.org/'),
 1094                 description('Base URI for relative resources')
 1095               ]).
 1096attribute_decl(source,
 1097               [ description('Name of the graph')
 1098               ]).
 1099attribute_decl(verifyData,
 1100               [ description('Verify the data (ignored)')
 1101               | Options
 1102               ]) :-
 1103    bool(off, Options).
 1104attribute_decl(schema,
 1105               [ description('Include schema RDF in downloaded graph')
 1106               | Options
 1107               ]) :-
 1108    bool(off, Options).
 1109attribute_decl(data,
 1110               [ description('Include non-schema RDF in downloaded graph')
 1111               | Options
 1112               ]) :-
 1113    bool(off, Options).
 1114attribute_decl(explicitOnly,
 1115               [ description('Do not include entailed triples')
 1116               | Options
 1117               ]) :-
 1118    bool(off, Options).
 1119attribute_decl(niceOutput,
 1120               [ description('Produce human-readable output (ignored; we always do that)')
 1121               | Options
 1122               ]) :-
 1123    bool(off, Options).
 1124attribute_decl(user,
 1125               [ description('User name')
 1126               ]).
 1127attribute_decl(password,
 1128               [ description('Clear-text password')
 1129               ]).
 1130
 1131                                        % Our extensions
 1132attribute_decl(storeAs,
 1133               [ default(''),
 1134                 description('Store query under this name')
 1135               ]).
 1136attribute_decl(persistent,
 1137               [ description('Modify persistency of a graph'),
 1138                 oneof([on, off])
 1139               ]).
 1140attribute_decl(uri,
 1141               [ description('URI')
 1142               ]).
 1143attribute_decl(prefix,
 1144               [ description('Prefix (abbreviation)')
 1145               ]).
 1146
 1147bool(Def,
 1148     [ default(Def),
 1149       oneof([on, off])
 1150     ]).
 result_format(+Request, ?Format) is det
 1155result_format(_Request, Format) :-
 1156    atom(Format),
 1157    !.
 1158result_format(Request, _Format) :-
 1159    memberchk(accept(Accept), Request),
 1160    debug(sparql(result), 'Got accept = ~q', [Accept]),
 1161    fail.
 1162result_format(_Request, xml).
 1163
 1164
 1165accept_output_format(Request, Format) :-
 1166    memberchk(accept(Accept), Request),
 1167    (   atom(Accept)
 1168    ->  http_parse_header_value(accept, Accept, Media)
 1169    ;   Media = Accept
 1170    ),
 1171    find_media(Media, Format),
 1172    !.
 1173accept_output_format(_, xml).
 1174
 1175find_media([media(Type, _, _, _)|T], Format) :-
 1176    (   sparql_media(Type, Format)
 1177    ->  true
 1178    ;   find_media(T, Format)
 1179    ).
 1180
 1181sparql_media(application/'sparql-results+xml',   xml).
 1182sparql_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.
 1193api_action(Request, G, html, Message) :-
 1194    !,
 1195    call_showing_messages(
 1196        api_action2(Request, G, html, Message),
 1197        [ header(h4(Message)),
 1198          footer([])
 1199        ]).
 1200api_action(Request, G, Format, Message) :-
 1201    api_action2(Request, G, Format, Message).
 1202
 1203api_action2(_Request, G, Format, Message) :-
 1204    logged_on(User, anonymous),
 1205    get_time(T0), T is integer(T0),
 1206    statistics(cputime, CPU0),
 1207    rdf_statistics(triples(Triples0)),
 1208    subjects(Subjects0),
 1209    run(G, sesame(User, T)),
 1210    subjects(Subjects1),
 1211    rdf_statistics(triples(Triples1)),
 1212    statistics(cputime, CPU1),
 1213    CPU is CPU1 - CPU0,
 1214    Triples is Triples1 - Triples0,
 1215    Subjects is Subjects1 - Subjects0,
 1216    done(Format, Message, CPU, Subjects, Triples).
 1217
 1218:- if(rdf_statistics(subjects(_))).     % RDF 2.x
 1219subjects(Count) :- rdf_statistics(subjects(Count)).
 1220subj_label --> html('Subjects').
 1221:- else.                                % RDF 3.0
 1222subjects(Count) :- rdf_statistics(resources(Count)).
 1223subj_label --> html('Resources').
 1224:- endif. 1225
 1226:- meta_predicate
 1227    run(0, +). 1228
 1229run(M:(A,B), Log) :-
 1230    !,
 1231    run(M:A, Log),
 1232    run(M:B, Log).
 1233run(Goal, _) :-
 1234    no_transaction(Goal),
 1235    !,
 1236    call(Goal).
 1237run(A, Log) :-
 1238    rdf_transaction(A, Log).
 1239
 1240no_transaction(_:rdf_reset_db).
 1241no_transaction(_:rdf_unload_graph(_)).
 1242no_transaction(_:rdf_flush_journals(_)).
 1243no_transaction(cpa_browse:multigraph_action(_,_)).
 1244
 1245done(html, _Message, CPU, Subjects, Triples) :-
 1246    after_messages([ \result_table(CPU, Subjects, Triples)
 1247                   ]).
 1248done(Format, _:Message, CPU, Subjects, Triples) :-
 1249    !,
 1250    done(Format, Message, CPU, Subjects, Triples).
 1251done(json, Fmt-Args, _CPU, _Subjects, _Triples) :-
 1252    format(string(Message), Fmt, Args),
 1253    format('Content-type: application/json~n~n'),
 1254    json_write(current_output,
 1255            json([transaction=
 1256                     json([status=
 1257                              json([msg=Message])])])),
 1258    format('~n').
 1259done(xml, Fmt-Args, _CPU, _Subjects, _Triples) :-
 1260    format(string(Message), Fmt, Args),
 1261    format('Content-type: text/xml~n~n'),
 1262    format('<transaction>~n'),
 1263    format('  <status>~n'),
 1264    format('     <msg>~w</msg>~n', [Message]),
 1265    format('  </status>~n'),
 1266    format('</transaction>~n').
 1267done(Format, Fmt-Args, _CPU, _Subjects, _Triples) :-
 1268    format('Content-type: text/plain~n~n'),
 1269    format('resultFormat=~w not yet supported~n~n', Format),
 1270    format(Fmt, Args).
 result_table(+CPU, +SubDiff, +TripleDiff)// is det
HTML component that summarises the result of an operation.
 1277result_table(CPU, Subjects, Triples) -->
 1278    { rdf_statistics(triples(TriplesNow)),
 1279      subjects(SubjectsNow)
 1280    },
 1281    html([ h4('Operation completed'),
 1282           table([ id('result'),
 1283                   class(block)
 1284                 ],
 1285                 [ tr([td(class(empty), ''), th('+/-'), th('now')]),
 1286                   tr([th(class(p_name), 'CPU time'),
 1287                       \nc('~3f', CPU), td('')]),
 1288                   tr([th(class(p_name), \subj_label),
 1289                       \nc('~D', Subjects), \nc('~D', SubjectsNow)]),
 1290                   tr([th(class(p_name), 'Triples'),
 1291                       \nc('~D', Triples), \nc('~D', TriplesNow)])
 1292                 ])
 1293         ]).
 authorized_api(+Action, +ResultFormat) is det
Errors
- permission_error(http_location, access, Path)
 1300authorized_api(Action, ResultFormat) :-
 1301    ResultFormat == html,          % do not bind
 1302    !,
 1303    authorized(Action).
 1304authorized_api(Action, _) :-
 1305    logged_on(User, anonymous),
 1306    check_permission(User, Action)