View source with raw comments or as raw
    1/*  Part of ClioPatria
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2013-2015, VU University Amsterdam
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- module(sparql_csv_result,
   31	  [ sparql_write_csv_result/3	% +Out, +Result, +Options
   32	  ]).   33:- use_module(library(csv)).   34:- use_module(library(assoc)).   35:- use_module(library(option)).   36:- use_module(library(sgml_write)).   37:- use_module(library(semweb/rdf_db)).   38:- if(exists_source(library(semweb/rdf11))).   39:- use_module(library(semweb/rdf11),
   40	      [ rdf_lexical_form/2
   41	      ]).   42:- endif.

Write SPARQL results as CSV

See also
- http://www.w3.org/TR/2013/REC-sparql11-results-csv-tsv-20130321/ */
   49sparql_csv_mime_type('text/tab-separated-values; charset=UTF-8').
 sparql_write_csv_result(+Out:stream, +Result, +Options) is det
Emit results from a SPARQL SELECT query as CSV. Options:
bnode_state(State0-State)
Maintain blank node mapping accross multiple calls. State0 is either a variable or a state returned by a previous call.
http_header(+Boolean)
if true (default), emit an HTTP Content-type header.
header_row(+Boolean)
if true (default), emit header row with binding names.
See also
- http://www.w3.org/TR/rdf-sparql-json-res/
   65sparql_write_csv_result(Out, select(VarTerm, Rows), Options) :- !,
   66	option(bnode_state(BNodes0-BNodes), Options, _),
   67	(   var(BNodes0)
   68	->  empty_assoc(BNodeDict),
   69	    BNodes0 = bnode(1, BNodeDict)
   70	;   true
   71	),
   72	rows_to_csv(Rows, CSVRows, BNodes0, BNodes),
   73	(   option(http_header(true), Options, true)
   74	->  sparql_csv_mime_type(ContentType),
   75	    format('Content-type: ~w~n~n', [ContentType])
   76	;   true
   77	),
   78	(   option(header_row(true), Options, true)
   79	->  csv_write_stream(Out, [VarTerm|CSVRows], [])
   80	;   csv_write_stream(Out, CSVRows, [])
   81	).
   82sparql_write_csv_result(_Out, Result, _Options) :- !,
   83	domain_error(csv_sparql_result, Result).
   84
   85rows_to_csv([], [], BNodeDict, BNodeDict).
   86rows_to_csv([H0|T0], [H|T], BNodeDict0, BNodeDict) :-
   87	row_to_csv(H0, H, BNodeDict0, BNodeDict1),
   88	rows_to_csv(T0, T, BNodeDict1, BNodeDict).
   89
   90row_to_csv(RDF, CSV, BNodeDict0, BNodeDict) :-
   91	RDF =.. [_|RDFFields],
   92	fields_to_csv(RDFFields, CSVFields, BNodeDict0, BNodeDict),
   93	CSV =.. [row|CSVFields].
   94
   95fields_to_csv([], [], BNodeDict, BNodeDict).
   96fields_to_csv([H0|T0], [H|T], BNodeDict0, BNodeDict) :-
   97	field_to_csv(H0, H, BNodeDict0, BNodeDict1),
   98	fields_to_csv(T0, T, BNodeDict1, BNodeDict).
   99
  100field_to_csv(Var, '', BNodeDict, BNodeDict) :-
  101	(   var(Var)
  102	->  true
  103	;   Var == '$null$'
  104	), !.
  105field_to_csv(literal(Literal), Text, BNodeDict, BNodeDict) :-
  106	literal_text(Literal, Text), !.
  107field_to_csv(@(LangString,Lang), Text, BNodeDict, BNodeDict) :-
  108	literal_text(@(LangString,Lang), Text), !.
  109field_to_csv(^^(Lexical,Type), Text, BNodeDict, BNodeDict) :-
  110	literal_text(^^(Lexical,Type), Text), !.
  111field_to_csv(Resource, BNode, BNodeDict0, BNodeDict) :-
  112	rdf_is_bnode(Resource), !,
  113	BNodeDict0 = bnode(N0, Dict0),
  114	(   get_assoc(Resource, Dict0, BNode)
  115	->  BNodeDict = BNodeDict0
  116	;   succ(N0, N),
  117	    atomic_list_concat(['_:node', N], BNode),
  118	    put_assoc(Resource, Dict0, BNode, Dict),
  119	    BNodeDict = bnode(N, Dict)
  120	).
  121field_to_csv(Atomic, Atomic, BNodeDict, BNodeDict) :-
  122	atomic(Atomic), !.
  123field_to_csv(Term, String, BNodeDict, BNodeDict) :-
  124	term_string(Term, String).
 literal_text(+Literal, -Value) is semidet
  128literal_text(type(Type, Value), Text) :- !,
  129	atom(Type),
  130	(   rdf_equal(Type, rdf:'XMLLiteral')
  131	->  with_output_to(string(Text),
  132			   xml_write(Value, [header(false)]))
  133	;   atomic(Value)
  134	->  Text = Value
  135	;   term_string(Value, Text)
  136	).
  137literal_text(lang(Lang, LangText), Text) :- !,
  138	atom(Lang),
  139	literal_text(LangText, Text).
  140literal_text(@(LangText, Lang), Text) :- !,
  141	atom(Lang),
  142	literal_text(LangText, Text).
  143:- if(current_predicate(rdf_lexical_form/2)).  144literal_text(^^(Lexical, Type), Text) :- !,
  145	rdf_lexical_form(^^(Lexical,Type), ^^(Text,_)).
  146:- endif.  147literal_text(Text, Text) :-
  148	atom(Text), !.
  149literal_text(Text, Text) :-
  150	string(Text), !.
  151
  152
  153		 /*******************************
  154		 *   INTERACTIVE QUERY RESULT	*
  155		 *******************************/
  156
  157:- multifile
  158	rdf_io:write_table/4.  159
  160rdf_io:write_table(csv, _, Rows, Options) :-
  161	memberchk(variables(Vars), Options), !,
  162	(   is_list(Vars)
  163	->  VarTerm =.. [vars|Vars]
  164	;   VarTerm = Vars
  165	),
  166	sparql_write_csv_result(current_output, select(VarTerm, Rows),
  167				[ content_type(text/plain),
  168				  Options
  169				])