Chris@0: /* $Id$ Chris@0: Chris@0: Part of SWI-Prolog Chris@0: Chris@0: Author: Jan Wielemaker Chris@0: E-mail: jan@swi.psy.uva.nl Chris@0: WWW: http://www.swi-prolog.org Chris@0: Copyright (C): 1985-2004, University of Amsterdam Chris@0: Chris@0: This program is free software; you can redistribute it and/or Chris@0: modify it under the terms of the GNU General Public License Chris@0: as published by the Free Software Foundation; either version 2 Chris@0: of the License, or (at your option) any later version. Chris@0: Chris@0: This program is distributed in the hope that it will be useful, Chris@0: but WITHOUT ANY WARRANTY; without even the implied warranty of Chris@0: MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the Chris@0: GNU General Public License for more details. Chris@0: Chris@0: You should have received a copy of the GNU Lesser General Public Chris@0: License along with this library; if not, write to the Free Software Chris@0: Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Chris@0: Chris@0: As a special exception, if you link this library with other files, Chris@0: compiled with a Free Software compiler, to produce an executable, this Chris@0: library does not by itself cause the resulting executable to be covered Chris@0: by the GNU General Public License. This exception does not however Chris@0: invalidate any other reasons why the executable file might be covered by Chris@0: the GNU General Public License. Chris@0: */ Chris@0: Chris@0: :- use_module(rdf_turtle). Chris@0: :- use_module(library(rdf_ntriples)). Chris@0: :- use_module(library('semweb/rdf_db')). Chris@0: Chris@0: /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - Chris@0: Handle the test-cases provided with the Turtle language definition. Chris@0: - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */ Chris@0: Chris@0: test_dir(Dir) :- Chris@0: atom_concat(Dir, '/*.ttl', Pattern), Chris@0: expand_file_name(Pattern, Files), Chris@0: maplist(test_file, Files). Chris@0: Chris@0: test_file(File) :- Chris@0: file_base_name(File, Base), Chris@0: atom_concat(bad, _, Base), !, Chris@0: file_base_name(File, BaseName), Chris@0: format('Negative test ~w ...', [BaseName]), flush_output, Chris@0: catch(load_turtle(File, _Triples), E, true), Chris@0: ( nonvar(E) Chris@0: -> format('ok~n') Chris@0: ; format(' SHOULD FAIL~n') Chris@0: ). Chris@0: test_file(File) :- Chris@0: file_base_name(File, BaseName), Chris@0: format('Test ~w ...', [BaseName]), flush_output, Chris@0: load_turtle(File, Triples), Chris@0: file_name_extension(Base, ttl, File), Chris@0: file_name_extension(Base, out, OkFile), Chris@0: load_rdf_ntriples(OkFile, OkTriples0), Chris@0: maplist(canonical_triple, OkTriples0, OkTriples), Chris@0: sort(Triples, Turtle), Chris@0: sort(OkTriples, OK), Chris@0: report_diff(OK, Turtle), Chris@0: format(' done~n'). Chris@0: Chris@0: load_turtle(File, Triples) :- Chris@0: file_base_name(File, Base), Chris@0: atom_concat('http://www.redland.opensource.ac.uk/raptor/tests/turtle/', Chris@0: Base, Chris@0: BaseURI), Chris@0: rdf_load_turtle_file(File, Triples, Chris@0: [ base_uri(BaseURI), Chris@0: anon_prefix(node(_)) Chris@0: ]). Chris@0: Chris@0: canonical_triple(rdf(S0, P0, O0), Chris@0: rdf(S, P, O)) :- Chris@0: canonical_node(S0, S), Chris@0: canonical_node(P0, P), Chris@0: canonical_node(O0, O). Chris@0: Chris@0: canonical_node(node(GenId), node(N)) :- Chris@0: atom_concat(genid, AN, GenId), !, Chris@0: atom_number(AN, N). Chris@0: canonical_node(Node, Node). Chris@0: Chris@0: report_diff(OK, Result) :- Chris@0: compare_triples(OK, Result, _), !. Chris@0: report_diff(OK, Result) :- Chris@0: subtract(OK, Result, Missing), Chris@0: subtract(Result, OK, TooMany), Chris@0: ( Missing \== [] Chris@0: -> length(Missing, NM), Chris@0: format('**************** ~D Omitted results:~n', [NM]), Chris@0: write_list(Missing) Chris@0: ; true Chris@0: ), Chris@0: ( TooMany \== [] Chris@0: -> length(TooMany, TM), Chris@0: format('**************** ~D Overcomplete results:~n', [TM]), Chris@0: write_list(TooMany) Chris@0: ; true Chris@0: ). Chris@0: Chris@0: write_list([]). Chris@0: write_list([H|T]) :- Chris@0: ( H =.. [row|Cols] Chris@0: -> write_cols(Cols), Chris@0: format(' .~n') Chris@0: ; H = rdf(S,P,O), Chris@0: write_cell(S), put(' '), Chris@0: write_cell(P), put(' '), Chris@0: write_cell(O), write(' .\n') Chris@0: ; format('~p~n', [H]) Chris@0: ), Chris@0: write_list(T). Chris@0: Chris@0: Chris@0: write_cols([]). Chris@0: write_cols([H|T]) :- Chris@0: write_cell(H), Chris@0: ( T == [] Chris@0: -> true Chris@0: ; put(' '), Chris@0: write_cols(T) Chris@0: ). Chris@0: Chris@0: write_cell(literal(X)) :- !, Chris@0: format('"~w"', [X]). Chris@0: write_cell(R) :- Chris@0: atom(R), Chris@0: rdf_global_id(NS:Id, R), !, Chris@0: format('<~w:~w>', [NS, Id]). Chris@0: write_cell('$null$') :- !, Chris@0: write('NULL'). Chris@0: write_cell(R) :- Chris@0: atom(R), !, Chris@0: format('', [R]). Chris@0: write_cell(X) :- Chris@0: format('~p', [X]). Chris@0: Chris@0: /******************************* Chris@0: * COMPARE * Chris@0: *******************************/ Chris@0: Chris@0: %% compare_triples(+PlRDF, +NTRDF, -Substitions) Chris@0: % Chris@0: % Compare two models and if they are equal, return a list of Chris@0: % PlID = NTID, mapping NodeID elements. Chris@0: Chris@0: Chris@0: compare_triples(A, B, Substitutions) :- Chris@0: compare_list(A, B, [], Substitutions), !. Chris@0: Chris@0: compare_list([], [], S, S). Chris@0: compare_list([H1|T1], In2, S0, S) :- Chris@0: select(H2, In2, T2), Chris@0: compare_triple(H1, H2, S0, S1), Chris@0: compare_list(T1, T2, S1, S). Chris@0: Chris@0: compare_triple(rdf(Subj1,P1,O1), rdf(Subj2, P2, O2), S0, S) :- Chris@0: compare_field(Subj1, Subj2, S0, S1), Chris@0: compare_field(P1, P2, S1, S2), Chris@0: compare_field(O1, O2, S2, S). Chris@0: Chris@0: compare_field(X, X, S, S) :- !. Chris@0: compare_field(literal(X), xml(X), S, S) :- !. % TBD Chris@0: compare_field(X, Id, S, S) :- Chris@0: memberchk(X=Id, S), !. Chris@0: compare_field(X, Y, S, [X=Y|S]) :- Chris@0: \+ memberchk(X=_, S), Chris@0: node_id(X), Chris@0: node_id(Y), Chris@0: debug(rdf_compare, 'Assume ~w = ~w~n', [X, Y]). Chris@0: Chris@0: node_id(node(_)) :- !. Chris@0: node_id(X) :- Chris@0: atom(X), Chris@0: sub_atom(X, 0, _, _, '__').