36
37:- module(rdf_compare,
38 [ rdf_equal_graphs/3 39 ]). 40:- if(exists_source(library(semweb/rdf_db))). 41:- use_module(library(semweb/rdf_db),[lang_equal/2,rdf_is_bnode/1]). 42:- endif. 43:- autoload(library(apply),[partition/4,maplist/3]). 44:- use_module(library(debug),[debug/3]). 45:- autoload(library(lists),[select/3]).
72rdf_equal_graphs(A, B, Substitutions) :-
73 sort(A, SA),
74 sort(B, SB),
75 partition(contains_bnodes, SA, VA, GA),
76 partition(contains_bnodes, SB, VB, GB),
77 ( GA == GB
78 -> true
79 ; maplist(compare_triple, GA, GB)
80 ),
81 compare_list(VA, VB, [], Substitutions),
82 !.
83
84contains_bnodes(rdf(S,P,O)) :-
85 ( node_id(S)
86 ; node_id(P)
87 ; node_id(O)
88 ),
89 !.
90
91compare_list([], [], S, S).
92compare_list([H1|T1], In2, S0, S) :-
93 select(H2, In2, T2),
94 compare_triple(H1, H2, S0, S1),
95 compare_list(T1, T2, S1, S).
96
97compare_triple(T1, T2) :-
98 compare_triple(T1,T2,[],[]).
99
100compare_triple(rdf(Subj1,P1,O1), rdf(Subj2, P2, O2), S0, S) :-
101 compare_field(Subj1, Subj2, S0, S1),
102 compare_field(P1, P2, S1, S2),
103 compare_field(O1, O2, S2, S).
104
105compare_field(X, X, S, S) :- !.
106compare_field(literal(X), xml(X), S, S) :- !. 107compare_field(literal(lang(L1,X)), literal(lang(L2,X)), S, S) :-
108 !,
109 lang_equal(L1, L2).
110compare_field(X, Id, S, S) :-
111 memberchk(X=Id, S),
112 !.
113compare_field(X, Y, S, [X=Y|S]) :-
114 \+ memberchk(X=_, S),
115 node_id(X),
116 node_id(Y),
117 debug(rdf_compare, 'Assume ~w = ~w~n', [X, Y]).
118
119node_id(node(_)) :- !.
120node_id(X) :-
121 rdf_is_bnode(X).
122
123:- if(\+current_predicate(rdf_is_bnode/1)). 124rdf_is_bnode(Node) :-
125 atom(Node),
126 sub_atom(Node, 0, _, _, '_:').
127:- endif. 128:- if(\+current_predicate(lang_equal/2)). 129lang_equal(X, Y) :-
130 downcase_atom(X, L),
131 downcase_atom(Y, L).
132:- endif.
Compare RDF graphs
This library provides predicates that compare RDF graphs. The current version only provides one predicate: rdf_equal_graphs/3 verifies that two graphs are identical after proper labeling of the blank nodes.
Future versions of this library may contain more advanced operations, such as diffing two graphs. */