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-2018, University of Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(xml_result,
   36          [ xml_write_result_table/3,   % +Out, +Rows, +Options
   37            xml_read_result_table/3,    % +In, -Rows, -VarNames
   38            xml_to_result_table/3       % +XML, -Rows, -VarNames
   39          ]).   40:- use_module(library(assoc)).   41:- use_module(library('semweb/rdf_db')).   42:- use_module(library(sgml)).   43
   44:- multifile
   45    rdf_io:write_table/4.   46
   47
   48                 /*******************************
   49                 *            WRITING           *
   50                 *******************************/
 write_table(+Format, +Serialization, +Rows, +Options)
Write a result table in Sesame compliant XML format.
Arguments:
Format- Must be xml
   58rdf_io:write_table(xml, _, Rows, Options) :-
   59    format('Transfer-encoding: chunked~n'),
   60    format('Content-type: text/xml; charset=UTF-8~n~n'),
   61    xml_write_result_table(current_output, Rows, Options).
   62
   63xml_write_result_table(Out, Rows, Options) :-
   64    format(Out, '<?xml version="1.0" encoding="UTF-8"?>~n~n', []),
   65    format(Out, '<tableQueryResult>~n', []),
   66    header(Out, Options),
   67    tuples(Out, Rows),
   68    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')).
   76header(Out, Options) :-
   77    memberchk(variables(Vars), Options),
   78    !,
   79    (   is_list(Vars)
   80    ->  Names = Vars
   81    ;   Vars =.. [_|Names]
   82    ),
   83    format(Out, '  <header>~n', []),
   84    column_names(Names, Out),
   85    format(Out, '  </header>~n', []).
   86header(_, _).
   87
   88column_names([], _).
   89column_names([H|T], Out) :-
   90    format(Out, '    <columnName>~w</columnName>~n', [H]),
   91    column_names(T, Out).
   92
   93tuples(Out, Rows) :-
   94    empty_assoc(Map),               % URL --> BnodeID
   95    tuples(Rows, Out, 1, Map).
   96
   97tuples([], _, _, _).
   98tuples([H|T], Out, BN0, Map0) :-
   99    H =.. [_|Columns],
  100    format(Out, '  <tuple>~n', []),
  101    columns(Columns, Out, BN0, BN, Map0, Map),
  102    format(Out, '  </tuple>~n', []),
  103    tuples(T, Out, BN, Map).
  104
  105columns([], _, BN, BN, Map, Map).
  106columns([H|T], Out, BN0, BN, Map0, Map) :-
  107    column(H, Out, BN0, BN1, Map0, Map1),
  108    columns(T, Out, BN1, BN, Map1, Map).
  109
  110column(Var, Out, BN, BN, Map, Map) :-
  111    var(Var),
  112    !,
  113    format(Out, '    <null/>~n', []).
  114column('$null$', Out, BN, BN, Map, Map) :-
  115    !,
  116    format(Out, '    <null/>~n', []).
  117column(literal(L), Out, BN, BN, Map, Map) :-
  118    !,
  119    literal(L, Out).
  120column(Anon, Out, BN, BN, Map, Map) :-
  121    get_assoc(Anon, Map, BNode),
  122    !,
  123    format(Out, '    <bNode>~w</bNode>~n', [BNode]).
  124column(Anon, Out, BN0, BN, Map0, Map) :-
  125    rdf_is_bnode(Anon),
  126    !,
  127    BN is BN0 + 1,
  128    atom_concat(node, BN, BNode),
  129    format(Out, '    <bNode>~w</bNode>~n', [BNode]),
  130    put_assoc(Anon, Map0, BNode, Map).
  131column(URI, Out, BN, BN, Map, Map) :-
  132    xml_quote_cdata(URI, QURI, utf8),
  133    format(Out, '    <uri>~w</uri>~n', [QURI]).
  134
  135literal(type(Type, String), Out) :-
  136    !,
  137    xml_quote_cdata(String, QString, utf8),
  138    format(Out, '    <literal dataType="~w">~w</literal>~n',
  139           [Type, QString]).
  140literal(lang(Lang, String), Out) :-
  141    !,
  142    xml_quote_cdata(String, QString, utf8),
  143    format(Out, '    <literal xml:lang="~w">~w</literal>~n', [Lang, QString]).
  144literal(String, Out) :-
  145    !,
  146    xml_quote_cdata(String, QString, utf8),
  147    format(Out, '    <literal>~w</literal>~n', [QString]).
  148
  149
  150                 /*******************************
  151                 *            READING           *
  152                 *******************************/
 xml_read_result_table(+In, -Rows, -VarNames)
Read an XML document from In and return the rows and variable names in there.
  159xml_read_result_table(In, Rows, VarNames) :-
  160    load_structure(stream(In), XML,
  161                   [ dialect(xml),
  162                     space(remove)
  163                   ]),
  164    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, ...).
  172xml_to_result_table([XML], Rows, VarNames) :-
  173    !,
  174    xml_to_result_table(XML, Rows, VarNames).
  175xml_to_result_table(element(tableQueryResult, _, Content), Rows, VarNames) :-
  176    phrase(result_table(Rows, VarNames), Content).
  177
  178result_table(Rows, VarNames) -->
  179    result_header(VarNames),
  180    result_rows(Rows).
  181
  182result_header(VarNames) -->
  183    [ element(header, _, Content)
  184    ],
  185    !,
  186    { phrase(column_names(Columns), Content),
  187      VarNames =.. [names|Columns]
  188    }.
  189result_header(names) -->
  190    [].
  191
  192column_names([]) -->
  193    [].
  194column_names([Name|T]) -->
  195    [ element(columnName, _, [Name])
  196    ],
  197    column_names(T).
  198
  199result_rows([Row|Rows]) -->
  200    [ element(tuple, _, Content)
  201    ],
  202    { phrase(columns(Columns), Content),
  203      Row =.. [row|Columns]
  204    },
  205    result_rows(Rows).
  206result_rows([]) -->
  207    [].
  208
  209columns([H|T]) -->
  210    column(H),
  211    !,
  212    columns(T).
  213columns([]) -->
  214    [].
  215
  216column(URI) -->
  217    [ element(uri, _, [URI])
  218    ],
  219    !.
  220column(Bnode) -->
  221    [ element(bNode, _, [Bnode])
  222    ],
  223    !.
  224column(literal(Literal)) -->
  225    [ element(literal, A, [String]) ],
  226    {   memberchk(datatype=Type, A)
  227    ->  Literal = type(Type, String)
  228    ;   memberchk('xml:lang'=Lang, A)
  229    ->  Literal = lang(Lang, String)
  230    ;   Literal = String
  231    }.
  232column('$null$') -->
  233    [ element(null, _, [])
  234    ],
  235    !