View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2010-2020, University of Amsterdam
    7                              VU University Amsterdam
    8                              SWI-Prolog Solutions b.v.
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(sparql_client,
   38          [ sparql_query/3,             % +Query, -Row, +Options
   39            sparql_set_server/1,        % +Options
   40            sparql_read_xml_result/2,   % +Stream, -Result
   41            sparql_read_json_result/2   % +Input, -Result
   42          ]).   43:- autoload(library(apply), [maplist/3, maplist/4, partition/4]).   44:- autoload(library(gensym), [gensym/2]).   45:- autoload(library(lists), [member/2]).   46:- autoload(library(option), [select_option/3, select_option/4, merge_options/3]).   47:- autoload(library(rdf), [load_rdf/2]).   48:- autoload(library(readutil), [read_stream_to_codes/2]).   49:- autoload(library(sgml), [load_structure/3]).   50:- autoload(library(uri),
   51            [ uri_components/2,
   52              uri_data/3,
   53              uri_authority_components/2,
   54              uri_authority_data/3
   55            ]).   56:- autoload(library(http/http_open), [http_open/3]).   57:- autoload(library(http/json), [json_read/2]).   58:- autoload(library(semweb/turtle), [rdf_read_turtle/3]).

SPARQL client library

This module provides a SPARQL client. For example:

?- sparql_query('select * where { ?x rdfs:label "Amsterdam" }', Row,
                [ host('dbpedia.org'), path('/sparql/')]).

Row = row('http://www.ontologyportal.org/WordNet#WN30-108949737') ;
false.

Or, querying a local server using an ASK query:

?- sparql_query('ask { owl:Class rdfs:label "Class" }', Row,
                [ host('localhost'), port(3020), path('/sparql/')]).
Row = true.

HTTPS servers are supported using the scheme(https) option:

?- sparql_query('select * where { ?x rdfs:label "Amsterdam"@nl }',
                Row,
                [ scheme(https),
                  host('query.wikidata.org'),
                  path('/sparql')
                ]).

*/

 sparql_query(+Query, -Result, +Options) is nondet
Execute a SPARQL query on an HTTP SPARQL endpoint. Query is an atom that denotes the query. Result is unified to a term rdf(S,P,O) for CONSTRUCT and DESCRIBE queries, row(...) for SELECT queries and true or false for ASK queries. Options are

Variables that are unbound in SPARQL (e.g., due to SPARQL optional clauses), are bound in Prolog to the atom '$null$'.

endpoint(+URL)
May be used as alternative to Scheme, Host, Port and Path to specify the endpoint in a single option.
host(+Host)
port(+Port)
path(+Path)
scheme(+Scheme)
The above four options set the location of the server.
search(+ListOfParams)
Provide additional query parameters, such as the graph.
variable_names(-ListOfNames)
Unifies ListOfNames with a list of atoms that describe the names of the variables in a SELECT query.

Remaining options are passed to http_open/3. The defaults for Host, Port and Path can be set using sparql_set_server/1. The initial default for port is 80 and path is `/sparql/`.

For example, the ClioPatria server understands the parameter entailment. The code below queries for all triples using _rdfs_entailment.

?- sparql_query('select * where { ?s ?p ?o }',
                Row,
                [ search([entailment=rdfs])
                ]).

Another useful option is the request_header which, for example, may be used to trick force a server to reply using a particular document format:

?- sparql_query(
       'select * where { ?s ?p ?o }',
        Row,
        [ host('integbio.jp'),
          path('/rdf/sparql'),
          request_header('Accept' =
                         'application/sparql-results+xml')
        ]).
  147sparql_query(Query, Row, Options) :-
  148    (   select_option(endpoint(URL), Options, Options5)
  149    ->  uri_components(URL, Components),
  150        uri_data(scheme, Components, Scheme),
  151        uri_data(authority, Components, Auth),
  152        uri_data(path, Components, Path),
  153        uri_data(search, Components, Extra),
  154        ignore(Extra = []),
  155        uri_authority_components(Auth, AComp),
  156        uri_authority_data(host, AComp, Host),
  157        uri_authority_data(port, AComp, Port),
  158        (   var(Port)
  159        ->  sparql_port(Scheme, Port, _, _)
  160        ;   true
  161        )
  162    ;   sparql_param(scheme(Scheme), Options,  Options1),
  163        sparql_port(Scheme, Port,    Options1, Options2),
  164        sparql_param(host(Host),     Options2, Options3),
  165        sparql_param(path(Path),     Options3, Options4),
  166        select_option(search(Extra), Options4, Options5, [])
  167    ),
  168    select_option(variable_names(VarNames), Options5, Options6, _),
  169    partition(is_url_option, Options6, UrlOptions, HTTPOptions),
  170    sparql_extra_headers(HTTPOptions0),
  171    merge_options(HTTPOptions, HTTPOptions0, HTTPOptions1),
  172    http_open([ scheme(Scheme),
  173                host(Host),
  174                port(Port),
  175                path(Path),
  176                search([ query = Query
  177                       | Extra
  178                       ])
  179              | UrlOptions
  180              ], In,
  181              [ header(content_type, ContentType),
  182                status_code(Status)
  183              | HTTPOptions1
  184              ]),
  185    plain_content_type(ContentType, CleanType),
  186    read_reply(Status, CleanType, In, VarNames, Row).
  187
  188url_option(scheme).
  189url_option(user).
  190url_option(password).
  191url_option(host).
  192url_option(port).
  193url_option(path).
  194url_option(query_string).
  195url_option(search).
  196
  197is_url_option(Name = _Value) :-
  198    url_option(Name),
  199    !.
  200is_url_option(Opt) :-
  201    compound(Opt),
  202    functor(Opt, Name, 1),
  203    url_option(Name).
 sparql_extra_headers(-List)
Send extra headers with the request. Note that, although we also process RDF embedded in HTML, we do not explicitely ask for it. Doing so causes some (e.g., http://w3.org/2004/02/skos/core to reply with the HTML description rather than the RDF).
  212sparql_extra_headers(
  213        [ request_header('Accept' = 'application/sparql-results+xml, \c
  214                                     application/n-triples, \c
  215                                     application/x-turtle; q=0.9, \c
  216                                     application/turtle; q=0.9, \c
  217                                     text/turtle, \c
  218                                     application/sparql-results+json, \c
  219                                     application/rdf+xml, \c
  220                                     text/rdf+xml; q=0.8, \c
  221                                     */*; q=0.1')
  222        ]).
 read_reply(+Status, +ContentType, +In, -Close, -Row)
  226read_reply(200, ContentType, In, Close, Row) :-
  227    !,
  228    read_reply(ContentType, In, Close, Row).
  229read_reply(Status, _ContentType, In, _Close, _Row) :-
  230    call_cleanup(read_string(In, _, Reply),
  231                 close(In, [force(true)])),
  232    throw(error(sparql_error(Status, Reply), _)).
  233
  234read_reply('application/rdf+xml', In, _, Row) :-
  235    !,
  236    call_cleanup(load_rdf(stream(In), RDF), close(In)),
  237    member(Row, RDF).
  238read_reply(MIME, In, _, Row) :-
  239    turtle_media_type(MIME),
  240    !,
  241    call_cleanup(rdf_read_turtle(stream(In), RDF, []), close(In)),
  242    member(Row, RDF).
  243read_reply(MIME, In, VarNames, Row) :-
  244    sparql_result_mime(MIME),
  245    !,
  246    call_cleanup(sparql_read_xml_result(stream(In), Result),
  247                 close(In)),
  248    varnames(Result, VarNames),
  249    xml_result(Result, Row).
  250read_reply(MIME, In, VarNames, Row) :-
  251    json_result_mime(MIME),
  252    !,
  253    call_cleanup(sparql_read_json_result(stream(In), Result),
  254                 close(In)),
  255    (   Result = select(VarNames, Rows)
  256    ->  member(Row, Rows)
  257    ;   Result = ask(True)
  258    ->  Row = True,
  259        VarNames = []
  260    ).
  261read_reply(Type, In, _, _) :-
  262    read_stream_to_codes(In, Codes),
  263    string_codes(Reply, Codes),
  264    close(In),
  265    throw(error(domain_error(sparql_result_document, Type),
  266                context(_, Reply))).
  267
  268turtle_media_type('application/x-turtle').
  269turtle_media_type('application/turtle').
  270turtle_media_type('application/n-triples').
  271turtle_media_type('text/rdf+n3').
  272turtle_media_type('text/turtle').
  273
  274sparql_result_mime('application/sparql-results+xml'). % official
  275sparql_result_mime('application/sparql-result+xml').
  276
  277json_result_mime('application/sparql-results+json').
  278
  279
  280plain_content_type(Type, Plain) :-
  281    sub_atom(Type, B, _, _, (;)),
  282    !,
  283    sub_string(Type, 0, B, _, Main),
  284    normalize_space(atom(Plain), Main).
  285plain_content_type(Type, Type).
  286
  287xml_result(ask(Bool), Result) :-
  288    !,
  289    Result = Bool.
  290xml_result(select(_VarNames, Rows), Result) :-
  291    member(Result, Rows).
  292
  293varnames(ask(_), _).
  294varnames(select(VarTerm, _Rows), VarNames) :-
  295    VarTerm =.. [_|VarNames].
  296
  297
  298                 /*******************************
  299                 *            SETTINGS          *
  300                 *******************************/
  301
  302:- dynamic
  303    sparql_setting/1.  304
  305sparql_setting(scheme(http)).
  306sparql_setting(path('/sparql/')).
  307
  308sparql_param(Param, Options0, Options) :-
  309    select_option(Param, Options0, Options),
  310    !.
  311sparql_param(Param, Options, Options) :-
  312    sparql_setting(Param),
  313    !.
  314sparql_param(Param, Options, Options) :-
  315    functor(Param, Name, _),
  316    throw(error(existence_error(option, Name), _)).
  317
  318sparql_port(_Scheme, Port, Options0, Options) :-
  319    select_option(port(Port), Options0, Options),
  320    !.
  321sparql_port(_Scheme, Port, Options, Options) :-
  322    sparql_setting(port(Port)),
  323    !.
  324sparql_port(http, 80, Options, Options) :-
  325    !.
  326sparql_port(https, 443, Options, Options) :-
  327    !.
 sparql_set_server(+OptionOrList)
Set sparql server default options. Provided defaults are: host, port and repository. For example:
    sparql_set_server([ host(localhost),
                        port(8080)
                        path(world)
                      ])

The default for port is 80 and path is /sparql/.

  344sparql_set_server([]) :- !.
  345sparql_set_server([H|T]) :-
  346    !,
  347    sparql_set_server(H),
  348    sparql_set_server(T).
  349sparql_set_server(Term) :-
  350    functor(Term, Name, Arity),
  351    functor(Unbound, Name, Arity),
  352    retractall(sparql_setting(Unbound)),
  353    assert(sparql_setting(Term)).
  354
  355
  356                 /*******************************
  357                 *             RESULT           *
  358                 *******************************/
  359
  360ns(sparql, 'http://www.w3.org/2005/sparql-results#').
  361
  362/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  363Read    the    SPARQL    XML    result     format    as    defined    in
  364http://www.w3.org/TR/rdf-sparql-XMLres/, version 6 April 2006.
  365- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  366
  367                 /*******************************
  368                 *        MACRO HANDLING        *
  369                 *******************************/
  370
  371%       substitute 'sparql' by the namespace   defined  above for better
  372%       readability of the remainder of the code.
  373
  374term_subst(V, _, _, V) :-
  375    var(V),
  376    !.
  377term_subst(F, F, T, T) :- !.
  378term_subst(C, F, T, C2) :-
  379    compound(C),
  380    !,
  381    functor(C, Name, Arity),
  382    functor(C2, Name, Arity),
  383    term_subst(0, Arity, C, F, T, C2).
  384term_subst(T, _, _, T).
  385
  386term_subst(A, A, _, _, _, _) :- !.
  387term_subst(I0, Arity, C0, F, T, C) :-
  388    I is I0 + 1,
  389    arg(I, C0, A0),
  390    term_subst(A0, F, T, A),
  391    arg(I, C, A),
  392    term_subst(I, Arity, C0, F, T, C).
  393
  394term_expansion(T0, T) :-
  395    ns(sparql, NS),
  396    term_subst(T0, sparql, NS, T).
  397
  398
  399                 /*******************************
  400                 *           READING            *
  401                 *******************************/
 sparql_read_xml_result(+Input, -Result)
Specs from http://www.w3.org/TR/rdf-sparql-XMLres/. The returned Result term is of the format:
select(VarNames, Rows)
Where VarNames is a term v(Name, ...) and Rows is a list of row(....) containing the column values in the same order as the variable names.
ask(Bool)
Where Bool is either true or false
  416:- thread_local
  417    bnode_map/2.  418
  419sparql_read_xml_result(Input, Result) :-
  420    load_structure(Input, DOM,
  421                   [ dialect(xmlns)
  422                   ]),
  423    call_cleanup(dom_to_result(DOM, Result),
  424                 retractall(bnode_map(_,_))).
  425
  426dom_to_result(DOM, Result) :-
  427    (   sub_element(DOM, sparql:head, _HAtt, Content)
  428    ->  variables(Content, Vars)
  429    ;   Vars = []
  430    ),
  431    (   Vars == [],
  432        sub_element(DOM, sparql:boolean, _, [TrueFalse])
  433    ->  Result = ask(TrueFalse)
  434    ;   VarTerm =.. [v|Vars],
  435        Result = select(VarTerm, Rows),
  436        sub_element(DOM, sparql:results, _RAtt, RContent)
  437    ->  rows(RContent, Vars, Rows)
  438    ),
  439    !.                                   % Guarantee finalization
 variables(+DOM, -Varnames)
Deals with <variable name=Name>. Head also may contain <link href="..."/>. This points to additional meta-data. Not really clear what we can do with that.
  447variables([], []).
  448variables([element(sparql:variable, Att, [])|T0], [Name|T]) :-
  449    !,
  450    memberchk(name=Name, Att),
  451    variables(T0, T).
  452variables([element(sparql:link, _, _)|T0], T) :-
  453    !,
  454    variables(T0, T).
  455variables([CDATA|T0], T) :-
  456    atomic(CDATA),
  457    variables(T0, T).
  458
  459
  460rows([], _, []).
  461rows([R|T0], Vars, [Row|T]) :-
  462    R = element(sparql:result, _, _),
  463    !,
  464    row_values(Vars, R, Values),
  465    Row =.. [row|Values],
  466    rows(T0, Vars, T).
  467rows([CDATA|T0], Vars, T) :-
  468    atomic(CDATA),
  469    rows(T0, Vars, T).
  470
  471row_values([], _, []).
  472row_values([Var|VarT], DOM, [Value|ValueT]) :-
  473    (   sub_element(DOM, sparql:binding, Att, Content),
  474        memberchk(name=Var, Att)
  475    ->  value(Content, Value)
  476    ;   Value = '$null$'
  477    ),
  478    row_values(VarT, DOM, ValueT).
  479
  480value([element(sparql:literal, Att, Content)|Rest], literal(Lit)) :-
  481    !,
  482    white(Rest),
  483    lit_value(Content, Value),
  484    (   memberchk(datatype=Type, Att)
  485    ->  Lit = type(Type, Value)
  486    ;   memberchk(xml:lang=Lang, Att)
  487    ->  Lit = lang(Lang, Value)
  488    ;   Lit = Value
  489    ).
  490value([element(sparql:uri, [], [URI])|Rest], URI) :- !,
  491    white(Rest).
  492value([element(sparql:bnode, [], [NodeID])|Rest], URI) :-
  493    !,
  494    white(Rest),
  495    bnode(NodeID, URI).
  496value([element(sparql:unbound, [], [])|Rest], '$null$') :-
  497    !,
  498    white(Rest).
  499value([CDATA|Rest], Value) :-
  500    atomic(CDATA),
  501    value(Rest, Value).
  502
  503
  504white([]).
  505white([CDATA|T]) :-
  506    atomic(CDATA),
  507    white(T).
  508
  509lit_value([], '').
  510lit_value([Value], Value).
 sub_element(+DOM, +Name, -Atttribs, -Content)
  515sub_element(element(Name, Att, Content), Name, Att, Content).
  516sub_element(element(_, _, List), Name, Att, Content) :-
  517    sub_element(List, Name, Att, Content).
  518sub_element([H|T], Name, Att, Content) :-
  519    (   sub_element(H, Name, Att, Content)
  520    ;   sub_element(T, Name, Att, Content)
  521    ).
  522
  523
  524bnode(Name, URI) :-
  525    bnode_map(Name, URI),
  526    !.
  527bnode(Name, URI) :-
  528    gensym('__bnode', URI0),
  529    assertz(bnode_map(Name, URI0)),
  530    URI = URI0.
 sparql_read_json_result(+Input, -Result) is det
The returned Result term is of the format:
select(VarNames, Rows)
Where VarNames is a term v(Name, ...) and Rows is a list of row(....) containing the column values in the same order as the variable names.
ask(Bool)
Where Bool is either true or false
See also
- http://www.w3.org/TR/rdf-sparql-json-res/
  547sparql_read_json_result(Input, Result) :-
  548    setup_call_cleanup(
  549        open_input(Input, In, Close),
  550        read_json_result(In, Result),
  551        close_input(Close)).
  552
  553open_input(stream(In), In, Close) :-
  554    !,
  555    encoding(In, utf8, Close).
  556open_input(In, In, Close) :-
  557    is_stream(In),
  558    !,
  559    encoding(In, utf8, Close).
  560open_input(File, In, close(In)) :-
  561    open(File, read, In, [encoding(utf8)]).
  562
  563encoding(In, Encoding, Close) :-
  564    stream_property(In, encoding(Old)),
  565    (   Encoding == Old
  566    ->  Close = true
  567    ;   set_stream(In, encoding(Encoding)),
  568        Close = set_stream(In, Encoding, Old)
  569    ).
  570
  571close_input(close(In)) :-
  572    !,
  573    retractall(bnode_map(_,_)),
  574    close(In).
  575close_input(_) :-
  576    retractall(bnode_map(_,_)).
  577
  578read_json_result(In, Result) :-
  579    json_read(In, JSON),
  580    json_to_result(JSON, Result).
  581
  582json_to_result(json([ head    = json(Head),
  583                      results = json(Body)
  584                    ]),
  585               select(Vars, Rows)) :-
  586    memberchk(vars=VarList, Head),
  587    Vars =.. [v|VarList],
  588    memberchk(bindings=Bindings, Body),
  589    !,
  590    maplist(json_row(VarList), Bindings, Rows).
  591json_to_result(json(JSon), ask(Boolean)) :-
  592    memberchk(boolean = @(Boolean), JSon).
  593
  594
  595json_row(Vars, json(Columns), Row) :-
  596    maplist(json_cell, Vars, Columns, Values),
  597    !,
  598    Row =.. [row|Values].
  599json_row(Vars, json(Columns), Row) :-
  600    maplist(json_cell_or_null(Columns), Vars, Values),
  601    Row =.. [row|Values].
  602
  603json_cell(Var, Var=json(JValue), Value) :-
  604    memberchk(type=Type, JValue),
  605    jvalue(Type, JValue, Value).
  606
  607json_cell_or_null(Columns, Var, Value) :-
  608    memberchk(Var=json(JValue), Columns),
  609    !,
  610    memberchk(type=Type, JValue),
  611    jvalue(Type, JValue, Value).
  612json_cell_or_null(_, _, '$null$').
  613
  614jvalue(uri, JValue, URI) :-
  615    memberchk(value=URI, JValue).
  616jvalue(literal, JValue, literal(Literal)) :-
  617    memberchk(value=Value, JValue),
  618    (   memberchk('xml:lang'=Lang, JValue)
  619    ->  Literal = lang(Lang, Value)
  620    ;   memberchk('datatype'=Type, JValue)
  621    ->  Literal = type(Type, Value)
  622    ;   Literal = Value
  623    ).
  624jvalue('typed-literal', JValue, literal(type(Type, Value))) :-
  625    memberchk(value=Value, JValue),
  626    memberchk('datatype'=Type, JValue).
  627jvalue(bnode, JValue, URI) :-
  628    memberchk(value=NodeID, JValue),
  629    bnode(NodeID, URI)