View source with raw comments or as raw
    1/*  $Id$
    2
    3    Part of SWI-Prolog
    4
    5    Author:        Jan Wielemaker
    6    E-mail:        J.Wielemaker@cs.vu.nl
    7    WWW:           http://www.swi-prolog.org
    8    Copyright (C): 2004-2010, University of Amsterdam
    9			      Vu University Amsterdam
   10
   11    This program is free software; you can redistribute it and/or
   12    modify it under the terms of the GNU General Public License
   13    as published by the Free Software Foundation; either version 2
   14    of the License, or (at your option) any later version.
   15
   16    This program is distributed in the hope that it will be useful,
   17    but WITHOUT ANY WARRANTY; without even the implied warranty of
   18    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   19    GNU General Public License for more details.
   20
   21    You should have received a copy of the GNU Lesser General Public
   22    License along with this library; if not, write to the Free Software
   23    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   24
   25    As a special exception, if you link this library with other files,
   26    compiled with a Free Software compiler, to produce an executable, this
   27    library does not by itself cause the resulting executable to be covered
   28    by the GNU General Public License. This exception does not however
   29    invalidate any other reasons why the executable file might be covered by
   30    the GNU General Public License.
   31*/
   32
   33:- module(sparql_xml_result,
   34	  [ sparql_write_xml_result/3	% +Stream, +Result
   35	  ]).   36:- use_module(library(sgml)).   37:- use_module(library(assoc)).   38:- use_module(library(option)).   39:- use_module(library('semweb/rdf_db'), [rdf_is_bnode/1, rdf_equal/2]).   40
   41ns(sparql, 'http://www.w3.org/2005/sparql-results#').
   42
   43/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   44Read/write   the   SPARQL   XML   result     format    as   defined   in
   45http://www.w3.org/TR/rdf-sparql-XMLres/, version 6 April 2006.
   46- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
   47
   48		 /*******************************
   49		 *	      WRITING		*
   50		 *******************************/
 sparql_write_xml_result(+Out, +Term, +Options)
Write SPARQL XML result data.
   56sparql_write_xml_result(Out, ask(TrueFalse), _Options) :- !,
   57	write_header(Out),
   58	format(Out, '  <head/>~n', []),
   59	format(Out, '  <boolean>~w</boolean>~n', [TrueFalse]),
   60	format(Out, '</sparql>~n', []).
   61sparql_write_xml_result(Out, update(TrueFalse), Options) :- !,
   62	sparql_write_xml_result(Out, ask(TrueFalse), Options).
   63sparql_write_xml_result(Out, select(VarTerm, Rows), Options) :-
   64	VarTerm =.. [_|VarNames],
   65	option(ordered(Ordered), Options, false),
   66	option(distinct(Distinct), Options, false),
   67	write_header(Out),
   68	format(Out, '  <head>~n', []),
   69	write_varnames(VarNames, Out),
   70	format(Out, '  </head>~n', []),
   71	format(Out, '  <results ordered="~w" distinct="~w">~n',
   72	       [Ordered, Distinct]),
   73	write_rows(Rows, VarNames, Out),
   74	format(Out, '  </results>~n', []),
   75	format(Out, '</sparql>~n', []).
   76
   77write_header(Out) :-
   78	xml_encoding(Out, Encoding),
   79	format(Out, '<?xml version="1.0" encoding="~w"?>~n', [Encoding]),
   80	ns(sparql, Prefix),
   81	format(Out, '<sparql xmlns="~w">~n', [Prefix]).
   82
   83xml_encoding(Out, Encoding) :-
   84	stream_property(Out, encoding(Enc)),
   85	(   xml_encoding_name(Enc, Encoding)
   86	->  true
   87	;   throw(error(domain_error(rdf_encoding, Enc), _))
   88	).
   89
   90xml_encoding_name(ascii,       'US-ASCII').
   91xml_encoding_name(iso_latin_1, 'ISO-8859-1').
   92xml_encoding_name(utf8,        'UTF-8').
   93
   94write_varnames([], _).
   95write_varnames([H|T], Out) :-
   96	stream_property(Out, encoding(Encoding)),
   97	xml_quote_attribute(H, Q, Encoding),
   98	format(Out, '    <variable name="~w"/>~n', [Q]),
   99	write_varnames(T, Out).
  100
  101write_rows(Rows, VarNames, Out) :-
  102	empty_assoc(BNodes),
  103	write_rows(Rows, VarNames, Out, state(0, BNodes), _).
  104
  105write_rows([], _, _, State, State).
  106write_rows([H|T], VarNames, Out, State0, State) :-
  107	write_row(H, VarNames, Out, State0, State1),
  108	write_rows(T, VarNames, Out, State1, State).
  109
  110write_row(Row, VarNames, Out, State0, State) :-
  111	format(Out, '    <result>~n', []),
  112	write_bindings(VarNames, 1, Row, Out, State0, State),
  113	format(Out, '    </result>~n', []).
  114
  115write_bindings([], _, _, _, State, State).
  116write_bindings([Name|T], I, Row, Out, State0, State) :-
  117	arg(I, Row, Value),
  118	write_binding(Value, Name, Out, State0, State1),
  119	I2 is I + 1,
  120	write_bindings(T, I2, Row, Out, State1, State).
  121
  122write_binding(Var, _, _, S, S) :- var(Var), !.
  123write_binding('$null$', _, _, S, S) :- !.
  124write_binding(Value, Name, Out, State0, State) :-
  125	stream_property(Out, encoding(Encoding)),
  126	xml_quote_attribute(Name, Q, Encoding),
  127	format(Out, '      <binding name="~w">~n', [Q]),
  128	write_binding_value(Value, Out, State0, State),
  129	format(Out, '      </binding>~n', []).
  130
  131write_binding_value(literal(Lit), Out, State, State) :- !,
  132	write_binding_literal(Lit, Out).
  133write_binding_value(URI, Out, State0, State) :-
  134	rdf_is_bnode(URI), !,
  135	bnode_id(URI, Id, State0, State),
  136	format(Out, '        <bnode>~w</bnode>~n', [Id]).
  137write_binding_value(URI, Out, State, State) :-
  138	stream_property(Out, encoding(Encoding)),
  139	xml_quote_cdata(URI, Q, Encoding),
  140	format(Out, '        <uri>~w</uri>~n', [Q]).
 write_binding_literal(+Literal, +Out) is det
Write Literal to Out. The first clause deals with XMLLiteral fields. The SPARQL documentation is rather vaque about how this should be handled. It might well be that we should write the xml into an atom and xml-escape that.
  149write_binding_literal(type(Type, DOM), Out) :-
  150	rdf_equal(Type, rdf:'XMLLiteral'),
  151	xml_is_dom(DOM), !,
  152	with_output_to(string(S),
  153		       xml_write(current_output, DOM,
  154				 [ header(false),
  155				   layout(false)
  156				 ])),
  157	stream_property(Out, encoding(Encoding)),
  158	xml_quote_cdata(S, QV, Encoding),
  159	format(Out, '        <literal datatype="~w">~w</literal>~n', [Type, QV]).
  160write_binding_literal(type(Type, Value), Out) :- !,
  161	stream_property(Out, encoding(Encoding)),
  162	xml_quote_attribute(Type, QT, Encoding),
  163	(   atom(Value)
  164	->  xml_quote_cdata(Value, QV, Encoding)
  165	;   QV = Value			% ok for numbers, etc.
  166	),
  167	format(Out, '        <literal datatype="~w">~w</literal>~n', [QT, QV]).
  168write_binding_literal(lang(L, Value), Out) :- !,
  169	stream_property(Out, encoding(Encoding)),
  170	xml_quote_cdata(Value, QV, Encoding),
  171	format(Out, '        <literal xml:lang="~w">~w</literal>~n', [L, QV]).
  172write_binding_literal(Value, Out) :- !,
  173	stream_property(Out, encoding(Encoding)),
  174	xml_quote_cdata(Value, QV, Encoding),
  175	format(Out, '        <literal>~w</literal>~n', [QV]).
  176
  177bnode_id(URI, Id, State0, State) :-
  178	State0 = state(N, Assoc),
  179	(   get_assoc(URI, Assoc, Id)
  180	->  State = State0
  181	;   N2 is N + 1,
  182	    Id = N2,			% number 1, ...
  183	    put_assoc(URI, Assoc, Id, Assoc2),
  184	    State = state(N2, Assoc2)
  185	)