Chris@0
|
1 /* $Id$
|
Chris@0
|
2
|
Chris@0
|
3 Part of SWI-Prolog
|
Chris@0
|
4
|
Chris@0
|
5 Author: Jan Wielemaker
|
Chris@0
|
6 E-mail: wielemak@science.uva.nl
|
Chris@0
|
7 WWW: http://www.swi-prolog.org
|
Chris@0
|
8 Copyright (C): 2004-2006, University of Amsterdam
|
Chris@0
|
9
|
Chris@0
|
10 This program is free software; you can redistribute it and/or
|
Chris@0
|
11 modify it under the terms of the GNU General Public License
|
Chris@0
|
12 as published by the Free Software Foundation; either version 2
|
Chris@0
|
13 of the License, or (at your option) any later version.
|
Chris@0
|
14
|
Chris@0
|
15 This program is distributed in the hope that it will be useful,
|
Chris@0
|
16 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Chris@0
|
17 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Chris@0
|
18 GNU General Public License for more details.
|
Chris@0
|
19
|
Chris@0
|
20 You should have received a copy of the GNU Lesser General Public
|
Chris@0
|
21 License along with this library; if not, write to the Free Software
|
Chris@0
|
22 Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
Chris@0
|
23
|
Chris@0
|
24 As a special exception, if you link this library with other files,
|
Chris@0
|
25 compiled with a Free Software compiler, to produce an executable, this
|
Chris@0
|
26 library does not by itself cause the resulting executable to be covered
|
Chris@0
|
27 by the GNU General Public License. This exception does not however
|
Chris@0
|
28 invalidate any other reasons why the executable file might be covered by
|
Chris@0
|
29 the GNU General Public License.
|
Chris@0
|
30 */
|
Chris@0
|
31
|
Chris@0
|
32 :- module(sparql_client,
|
Chris@0
|
33 [ sparql_query/3, % +Query, -Row, +Options
|
Chris@0
|
34 sparql_set_server/1 % +Options
|
Chris@0
|
35 ]).
|
Chris@0
|
36 :- use_module(library('http/http_open')).
|
Chris@0
|
37 :- use_module(sparql_xml_result).
|
Chris@0
|
38 :- use_module(library(lists)).
|
Chris@0
|
39 :- use_module(library(rdf)).
|
Chris@0
|
40
|
Chris@0
|
41
|
Chris@0
|
42 %% sparql_query(+Query, -Result, +Options) is nondet.
|
Chris@0
|
43 %
|
Chris@0
|
44 % Execute a SPARQL query on an HTTP SPARQL endpoint. Query is an
|
Chris@0
|
45 % atom that denotes the query. Result is unified to a term
|
Chris@0
|
46 % rdf(S,P,O) for =construct= queries and row(...) for =select=
|
Chris@0
|
47 % queries.
|
Chris@0
|
48
|
Chris@0
|
49 sparql_query(Query, Row, Options) :-
|
Chris@0
|
50 sparql_param(host(Host), Options),
|
Chris@0
|
51 sparql_param(port(Port), Options),
|
Chris@0
|
52 sparql_param(path(Path), Options),
|
Chris@0
|
53 http_open([ protocol(http),
|
Chris@0
|
54 host(Host),
|
Chris@0
|
55 port(Port),
|
Chris@0
|
56 path(Path),
|
Chris@0
|
57 search([ query = Query
|
Chris@0
|
58 ])
|
Chris@0
|
59 ], In,
|
Chris@0
|
60 [ header(content_type, ContentType)
|
Chris@0
|
61 ]),
|
Chris@0
|
62 plain_content_type(ContentType, CleanType),
|
Chris@0
|
63 read_reply(CleanType, In, Row).
|
Chris@0
|
64
|
Chris@0
|
65 read_reply('application/rdf+xml', In, Row) :- !,
|
Chris@0
|
66 call_cleanup(load_rdf(stream(In), RDF), close(In)),
|
Chris@0
|
67 member(Row, RDF).
|
Chris@0
|
68 read_reply('application/sparql-result+xml', In, Row) :- !,
|
Chris@0
|
69 call_cleanup(sparql_read_xml_result(stream(In), Result),
|
Chris@0
|
70 close(In)),
|
Chris@0
|
71 xml_result(Result, Row).
|
Chris@0
|
72 read_reply(Type, In, _) :-
|
Chris@0
|
73 close(In),
|
Chris@0
|
74 throw(error(domain_error(sparql_result_document, Type), _)).
|
Chris@0
|
75
|
Chris@0
|
76 plain_content_type(Type, Plain) :-
|
Chris@0
|
77 sub_atom(Type, B, _, _, (;)), !,
|
Chris@0
|
78 sub_string(Type, 0, B, _, Main),
|
Chris@0
|
79 normalize_space(atom(Plain), Main).
|
Chris@0
|
80 plain_content_type(Type, Type).
|
Chris@0
|
81
|
Chris@0
|
82 xml_result(ask(Bool), Result) :- !,
|
Chris@0
|
83 Result = Bool.
|
Chris@0
|
84 xml_result(select(_VarNames, Rows), Result) :-
|
Chris@0
|
85 member(Result, Rows).
|
Chris@0
|
86
|
Chris@0
|
87
|
Chris@0
|
88
|
Chris@0
|
89
|
Chris@0
|
90
|
Chris@0
|
91 /*******************************
|
Chris@0
|
92 * SETTINGS *
|
Chris@0
|
93 *******************************/
|
Chris@0
|
94
|
Chris@0
|
95 :- dynamic
|
Chris@0
|
96 sparql_setting/1.
|
Chris@0
|
97
|
Chris@0
|
98 sparql_param(Param, Options) :-
|
Chris@0
|
99 memberchk(Param, Options), !.
|
Chris@0
|
100 sparql_param(Param, _Options) :-
|
Chris@0
|
101 sparql_setting(Param), !.
|
Chris@0
|
102 sparql_param(Param, _Options) :-
|
Chris@0
|
103 functor(Param, Name, _),
|
Chris@0
|
104 throw(error(existence_error(option, Name), _)).
|
Chris@0
|
105
|
Chris@0
|
106 %% sparql_set_server(+OptionOrList)
|
Chris@0
|
107 %
|
Chris@0
|
108 % Set sparql server default options. Provided defaults are:
|
Chris@0
|
109 % host, port and repository. For example:
|
Chris@0
|
110 %
|
Chris@0
|
111 %% set_sparql_default([ host(localhost),
|
Chris@0
|
112 %% port(8080)
|
Chris@0
|
113 %% repository(world)
|
Chris@0
|
114 % ])
|
Chris@0
|
115
|
Chris@0
|
116 sparql_set_server([]) :- !.
|
Chris@0
|
117 sparql_set_server([H|T]) :- !,
|
Chris@0
|
118 sparql_set_server(H),
|
Chris@0
|
119 sparql_set_server(T).
|
Chris@0
|
120 sparql_set_server(Term) :-
|
Chris@0
|
121 functor(Term, Name, Arity),
|
Chris@0
|
122 functor(Unbound, Name, Arity),
|
Chris@0
|
123 retractall(sparql_setting(Unbound)),
|
Chris@0
|
124 assert(sparql_setting(Term)).
|