View source with raw comments or as raw
    1/*  $Id$
    2
    3    Part of SWI-Prolog
    4
    5    Author:        Jan Wielemaker
    6    E-mail:        jan@swi.psy.uva.nl
    7    WWW:           http://www.swi-prolog.org
    8    Copyright (C): 1985-2004, University of Amsterdam
    9
   10    This program is free software; you can redistribute it and/or
   11    modify it under the terms of the GNU General Public License
   12    as published by the Free Software Foundation; either version 2
   13    of the License, or (at your option) any later version.
   14
   15    This program is distributed in the hope that it will be useful,
   16    but WITHOUT ANY WARRANTY; without even the implied warranty of
   17    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   18    GNU General Public License for more details.
   19
   20    You should have received a copy of the GNU Lesser General Public
   21    License along with this library; if not, write to the Free Software
   22    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   23
   24    As a special exception, if you link this library with other files,
   25    compiled with a Free Software compiler, to produce an executable, this
   26    library does not by itself cause the resulting executable to be covered
   27    by the GNU General Public License. This exception does not however
   28    invalidate any other reasons why the executable file might be covered by
   29    the GNU General Public License.
   30*/
   31
   32:- module(xml_result,
   33	  [ xml_write_result_table/3,	% +Out, +Rows, +Options
   34	    xml_read_result_table/3,	% +In, -Rows, -VarNames
   35	    xml_to_result_table/3	% +XML, -Rows, -VarNames
   36	  ]).   37:- use_module(library(assoc)).   38:- use_module(library('semweb/rdf_db')).   39:- use_module(library(sgml)).   40
   41:- multifile
   42	rdf_io:write_table/4.   43
   44
   45		 /*******************************
   46		 *	      WRITING		*
   47		 *******************************/
 write_table(+Format, +Serialization, +Rows, +Options)
Write a result table in Sesame compliant XML format.
Arguments:
Format- Must be xml
   55rdf_io:write_table(xml, _, Rows, Options) :-
   56	format('Transfer-encoding: chunked~n'),
   57	format('Content-type: text/xml; charset=UTF-8~n~n'),
   58	xml_write_result_table(current_output, Rows, Options).
   59
   60xml_write_result_table(Out, Rows, Options) :-
   61	format(Out, '<?xml version="1.0" encoding="UTF-8"?>~n~n', []),
   62	format(Out, '<tableQueryResult>~n', []),
   63	header(Out, Options),
   64	tuples(Out, Rows),
   65	format(Out, '</tableQueryResult>~n', []).
 header(+Out, +Options) is det
Write the column-names obtained from the variables(+Vars) option. Vars is either a list of atoms or a term holding the comlumn names as arguments (as in v('Name', 'Age')).
   73header(Out, Options) :-
   74	memberchk(variables(Vars), Options), !,
   75	(   is_list(Vars)
   76	->  Names = Vars
   77	;   Vars =.. [_|Names]
   78	),
   79	format(Out, '  <header>~n', []),
   80	column_names(Names, Out),
   81	format(Out, '  </header>~n', []).
   82header(_, _).
   83
   84column_names([], _).
   85column_names([H|T], Out) :-
   86	format(Out, '    <columnName>~w</columnName>~n', [H]),
   87	column_names(T, Out).
   88
   89tuples(Out, Rows) :-
   90	empty_assoc(Map),		% URL --> BnodeID
   91	tuples(Rows, Out, 1, Map).
   92
   93tuples([], _, _, _).
   94tuples([H|T], Out, BN0, Map0) :-
   95	H =.. [_|Columns],
   96	format(Out, '  <tuple>~n', []),
   97	columns(Columns, Out, BN0, BN, Map0, Map),
   98	format(Out, '  </tuple>~n', []),
   99	tuples(T, Out, BN, Map).
  100
  101columns([], _, BN, BN, Map, Map).
  102columns([H|T], Out, BN0, BN, Map0, Map) :-
  103	column(H, Out, BN0, BN1, Map0, Map1),
  104	columns(T, Out, BN1, BN, Map1, Map).
  105
  106column(Var, Out, BN, BN, Map, Map) :-
  107	var(Var), !,
  108	format(Out, '    <null/>~n', []).
  109column('$null$', Out, BN, BN, Map, Map) :- !,
  110	format(Out, '    <null/>~n', []).
  111column(literal(L), Out, BN, BN, Map, Map) :- !,
  112	literal(L, Out).
  113column(Anon, Out, BN, BN, Map, Map) :-
  114	get_assoc(Anon, Map, BNode), !,
  115	format(Out, '    <bNode>~w</bNode>~n', [BNode]).
  116column(Anon, Out, BN0, BN, Map0, Map) :-
  117	rdf_is_bnode(Anon), !,
  118	BN is BN0 + 1,
  119	atom_concat(node, BN, BNode),
  120	format(Out, '    <bNode>~w</bNode>~n', [BNode]),
  121	put_assoc(Anon, Map0, BNode, Map).
  122column(URI, Out, BN, BN, Map, Map) :-
  123	xml_quote_cdata(URI, QURI, utf8),
  124	format(Out, '    <uri>~w</uri>~n', [QURI]).
  125
  126literal(type(Type, String), Out) :- !,
  127	xml_quote_cdata(String, QString, utf8),
  128	format(Out, '    <literal dataType="~w">~w</literal>~n',
  129	       [Type, QString]).
  130literal(lang(Lang, String), Out) :- !,
  131	xml_quote_cdata(String, QString, utf8),
  132	format(Out, '    <literal xml:lang="~w">~w</literal>~n', [Lang, QString]).
  133literal(String, Out) :- !,
  134	xml_quote_cdata(String, QString, utf8),
  135	format(Out, '    <literal>~w</literal>~n', [QString]).
  136
  137
  138		 /*******************************
  139		 *	      READING		*
  140		 *******************************/
 xml_read_result_table(+In, -Rows, -VarNames)
Read an XML document from In and return the rows and variable names in there.
  147xml_read_result_table(In, Rows, VarNames) :-
  148	load_structure(stream(In), XML,
  149		       [ dialect(xml),
  150			 space(remove)
  151		       ]),
  152	xml_to_result_table(XML, Rows, VarNames).
 xml_to_result_table(+XML, -Rows, -VarNames)
Convert a parsed XML document into a list of rows and a column name (variable name) term of the format names(Col1, Col2, ...).
  160xml_to_result_table([XML], Rows, VarNames) :- !,
  161	xml_to_result_table(XML, Rows, VarNames).
  162xml_to_result_table(element(tableQueryResult, _, Content), Rows, VarNames) :-
  163	phrase(result_table(Rows, VarNames), Content).
  164
  165result_table(Rows, VarNames) -->
  166	result_header(VarNames),
  167	result_rows(Rows).
  168
  169result_header(VarNames) -->
  170	[ element(header, _, Content)
  171	], !,
  172	{ phrase(column_names(Columns), Content),
  173	  VarNames =.. [names|Columns]
  174	}.
  175result_header(names) -->
  176	[].
  177
  178column_names([]) -->
  179	[].
  180column_names([Name|T]) -->
  181	[ element(columnName, _, [Name])
  182	],
  183	column_names(T).
  184
  185result_rows([Row|Rows]) -->
  186	[ element(tuple, _, Content)
  187	],
  188	{ phrase(columns(Columns), Content),
  189	  Row =.. [row|Columns]
  190	},
  191	result_rows(Rows).
  192result_rows([]) -->
  193	[].
  194
  195columns([H|T]) -->
  196	column(H), !,
  197	columns(T).
  198columns([]) -->
  199	[].
  200
  201column(URI) -->
  202	[ element(uri, _, [URI])
  203	], !.
  204column(Bnode) -->
  205	[ element(bNode, _, [Bnode])
  206	], !.
  207column(literal(Literal)) -->
  208	[ element(literal, A, [String]) ],
  209	{   memberchk(datatype=Type, A)
  210	->  Literal = type(Type, String)
  211	;   memberchk('xml:lang'=Lang, A)
  212	->  Literal = lang(Lang, String)
  213	;   Literal = String
  214	}.
  215column('$null$') -->
  216	[ element(null, _, [])
  217	], !