annotate jamendo/sparql-archived/SeRQL/turtle_test.pl @ 27:d95e683fbd35 tip

Enable CORS on urispace redirects as well
author Chris Cannam
date Tue, 20 Feb 2018 14:52:02 +0000
parents df9685986338
children
rev   line source
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: jan@swi.psy.uva.nl
Chris@0 7 WWW: http://www.swi-prolog.org
Chris@0 8 Copyright (C): 1985-2004, 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 :- use_module(rdf_turtle).
Chris@0 33 :- use_module(library(rdf_ntriples)).
Chris@0 34 :- use_module(library('semweb/rdf_db')).
Chris@0 35
Chris@0 36 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
Chris@0 37 Handle the test-cases provided with the Turtle language definition.
Chris@0 38 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
Chris@0 39
Chris@0 40 test_dir(Dir) :-
Chris@0 41 atom_concat(Dir, '/*.ttl', Pattern),
Chris@0 42 expand_file_name(Pattern, Files),
Chris@0 43 maplist(test_file, Files).
Chris@0 44
Chris@0 45 test_file(File) :-
Chris@0 46 file_base_name(File, Base),
Chris@0 47 atom_concat(bad, _, Base), !,
Chris@0 48 file_base_name(File, BaseName),
Chris@0 49 format('Negative test ~w ...', [BaseName]), flush_output,
Chris@0 50 catch(load_turtle(File, _Triples), E, true),
Chris@0 51 ( nonvar(E)
Chris@0 52 -> format('ok~n')
Chris@0 53 ; format(' SHOULD FAIL~n')
Chris@0 54 ).
Chris@0 55 test_file(File) :-
Chris@0 56 file_base_name(File, BaseName),
Chris@0 57 format('Test ~w ...', [BaseName]), flush_output,
Chris@0 58 load_turtle(File, Triples),
Chris@0 59 file_name_extension(Base, ttl, File),
Chris@0 60 file_name_extension(Base, out, OkFile),
Chris@0 61 load_rdf_ntriples(OkFile, OkTriples0),
Chris@0 62 maplist(canonical_triple, OkTriples0, OkTriples),
Chris@0 63 sort(Triples, Turtle),
Chris@0 64 sort(OkTriples, OK),
Chris@0 65 report_diff(OK, Turtle),
Chris@0 66 format(' done~n').
Chris@0 67
Chris@0 68 load_turtle(File, Triples) :-
Chris@0 69 file_base_name(File, Base),
Chris@0 70 atom_concat('http://www.redland.opensource.ac.uk/raptor/tests/turtle/',
Chris@0 71 Base,
Chris@0 72 BaseURI),
Chris@0 73 rdf_load_turtle_file(File, Triples,
Chris@0 74 [ base_uri(BaseURI),
Chris@0 75 anon_prefix(node(_))
Chris@0 76 ]).
Chris@0 77
Chris@0 78 canonical_triple(rdf(S0, P0, O0),
Chris@0 79 rdf(S, P, O)) :-
Chris@0 80 canonical_node(S0, S),
Chris@0 81 canonical_node(P0, P),
Chris@0 82 canonical_node(O0, O).
Chris@0 83
Chris@0 84 canonical_node(node(GenId), node(N)) :-
Chris@0 85 atom_concat(genid, AN, GenId), !,
Chris@0 86 atom_number(AN, N).
Chris@0 87 canonical_node(Node, Node).
Chris@0 88
Chris@0 89 report_diff(OK, Result) :-
Chris@0 90 compare_triples(OK, Result, _), !.
Chris@0 91 report_diff(OK, Result) :-
Chris@0 92 subtract(OK, Result, Missing),
Chris@0 93 subtract(Result, OK, TooMany),
Chris@0 94 ( Missing \== []
Chris@0 95 -> length(Missing, NM),
Chris@0 96 format('**************** ~D Omitted results:~n', [NM]),
Chris@0 97 write_list(Missing)
Chris@0 98 ; true
Chris@0 99 ),
Chris@0 100 ( TooMany \== []
Chris@0 101 -> length(TooMany, TM),
Chris@0 102 format('**************** ~D Overcomplete results:~n', [TM]),
Chris@0 103 write_list(TooMany)
Chris@0 104 ; true
Chris@0 105 ).
Chris@0 106
Chris@0 107 write_list([]).
Chris@0 108 write_list([H|T]) :-
Chris@0 109 ( H =.. [row|Cols]
Chris@0 110 -> write_cols(Cols),
Chris@0 111 format(' .~n')
Chris@0 112 ; H = rdf(S,P,O),
Chris@0 113 write_cell(S), put(' '),
Chris@0 114 write_cell(P), put(' '),
Chris@0 115 write_cell(O), write(' .\n')
Chris@0 116 ; format('~p~n', [H])
Chris@0 117 ),
Chris@0 118 write_list(T).
Chris@0 119
Chris@0 120
Chris@0 121 write_cols([]).
Chris@0 122 write_cols([H|T]) :-
Chris@0 123 write_cell(H),
Chris@0 124 ( T == []
Chris@0 125 -> true
Chris@0 126 ; put(' '),
Chris@0 127 write_cols(T)
Chris@0 128 ).
Chris@0 129
Chris@0 130 write_cell(literal(X)) :- !,
Chris@0 131 format('"~w"', [X]).
Chris@0 132 write_cell(R) :-
Chris@0 133 atom(R),
Chris@0 134 rdf_global_id(NS:Id, R), !,
Chris@0 135 format('<~w:~w>', [NS, Id]).
Chris@0 136 write_cell('$null$') :- !,
Chris@0 137 write('NULL').
Chris@0 138 write_cell(R) :-
Chris@0 139 atom(R), !,
Chris@0 140 format('<!~w>', [R]).
Chris@0 141 write_cell(X) :-
Chris@0 142 format('~p', [X]).
Chris@0 143
Chris@0 144 /*******************************
Chris@0 145 * COMPARE *
Chris@0 146 *******************************/
Chris@0 147
Chris@0 148 %% compare_triples(+PlRDF, +NTRDF, -Substitions)
Chris@0 149 %
Chris@0 150 % Compare two models and if they are equal, return a list of
Chris@0 151 % PlID = NTID, mapping NodeID elements.
Chris@0 152
Chris@0 153
Chris@0 154 compare_triples(A, B, Substitutions) :-
Chris@0 155 compare_list(A, B, [], Substitutions), !.
Chris@0 156
Chris@0 157 compare_list([], [], S, S).
Chris@0 158 compare_list([H1|T1], In2, S0, S) :-
Chris@0 159 select(H2, In2, T2),
Chris@0 160 compare_triple(H1, H2, S0, S1),
Chris@0 161 compare_list(T1, T2, S1, S).
Chris@0 162
Chris@0 163 compare_triple(rdf(Subj1,P1,O1), rdf(Subj2, P2, O2), S0, S) :-
Chris@0 164 compare_field(Subj1, Subj2, S0, S1),
Chris@0 165 compare_field(P1, P2, S1, S2),
Chris@0 166 compare_field(O1, O2, S2, S).
Chris@0 167
Chris@0 168 compare_field(X, X, S, S) :- !.
Chris@0 169 compare_field(literal(X), xml(X), S, S) :- !. % TBD
Chris@0 170 compare_field(X, Id, S, S) :-
Chris@0 171 memberchk(X=Id, S), !.
Chris@0 172 compare_field(X, Y, S, [X=Y|S]) :-
Chris@0 173 \+ memberchk(X=_, S),
Chris@0 174 node_id(X),
Chris@0 175 node_id(Y),
Chris@0 176 debug(rdf_compare, 'Assume ~w = ~w~n', [X, Y]).
Chris@0 177
Chris@0 178 node_id(node(_)) :- !.
Chris@0 179 node_id(X) :-
Chris@0 180 atom(X),
Chris@0 181 sub_atom(X, 0, _, _, '__').