/* This file is part of ClioPatria. Author: HTTP: http://e-culture.multimedian.nl/ GITWEB: http://gollem.science.uva.nl/git/ClioPatria.git GIT: git://gollem.science.uva.nl/home/git/ClioPatria.git GIT: http://gollem.science.uva.nl/home/git/ClioPatria.git Copyright: 2007, E-Culture/MultimediaN ClioPatria is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 2 of the License, or (at your option) any later version. ClioPatria is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with ClioPatria. If not, see . */ :- module(owl_ultra_lite, [ owl/3, owl/4, owl_subj/4, owl_similar/3, owl_similar/4, owl_inv/3, owl_inv/4, owl_same_inv/3, owl_same_inv/4, same/2, similar/2, inverse_predicate/2, % +P, -IP equivalence_set/2 % +URI, -EquivalenceSet ]). :- use_module(library(assoc)). :- use_module(library(error)). :- use_module(library(semweb/rdf_db)). rdf_optimise:rdf_db_goal(owl(S,P,O), S,P,O). rdf_optimise:subj_branch_factor(owl(_,_,_), X, rdfs_subject_branch_factor(X)). rdf_optimise:obj_branch_factor(owl(_,_,_), X, rdfs_object_branch_factor(X)). rdf_optimise:rdf_db_goal(owl(S,P,O,_), S,P,O). rdf_optimise:subj_branch_factor(owl(_,_,_,_), X, rdfs_subject_branch_factor(X)). rdf_optimise:obj_branch_factor(owl(_,_,_,_), X, rdfs_object_branch_factor(X)). :- rdf_meta owl(r,r,o), owl(r,r,o,?), owl_inv(r,r,o), owl_inv(r,r,o,?), owl_same_inv(r,r,o), owl_same_inv(r,r,o,?), owl_similar(r,r,o), owl_similar(r,r,o,?), inverse_predicate(r,r). %% owl(?S, ?P, ?O, ?RealP) is nondet. % % True if rdf_has(S1,P,O1,RealP) is true and S,S1 as well as O,O1 are % reachable using owl:sameAs. owl(S,P,O) :- owl(S,P,O,_). owl(S,P,O,P) :- %sorry we can't do subproperty here atom(P), rdf_equal(owl:sameAs, P), !, same(S,O). owl(S,P,O,SP) :- instantiated(S,O,I), owl(I,S,P,O,SP). owl_subj(S,P,V,Value) :- same(V, Value), rdf_has(S, P, Value). instantiated(S,O,I) :- ( atom(S) -> I0 = 0b10 ; I0 = 0b00 ), ( atom(O) -> I is I0\/0b01 ; I is I0\/0b00 ). owl(0b00, S,P,O,SP) :- rdf_value(S,P,O,SP). owl(0b10, S,P,O,SP) :- same(S, S0), rdf_value(S0,P,O,SP). owl(0b01, S,P,O,SP) :- same(O, O0), rdf_value(S,P,O0,SP). owl(0b11, S,P,O,SP) :- same(S, S0), same(O, O0), rdf_value(S0,P,O0,SP). rdf_value(S,P,O,SP) :- rdf_has(S,P,O,SP). rdf_value(S,P,O,SP) :- nonvar(O), !, rdf(S1,rdf:value,O), rdf_has(S,P,S1,SP). %% owl_similar(?S, ?P, ?O, ?RealP) is nondet. % % Behaves the same as owl/3, but also uses skos:exactMatch. owl_similar(S,P,O) :- owl_similar(S,P,O,_). owl_similar(S,P,O,P) :- %sorry we can't do subproperty here atom(P), ( rdf_equal(owl:sameAs, P) ; rdf_equal(skos:exactMatch, P) ), !, similar(S,O). owl_similar(S,P,O,SP) :- instantiated(S,O,I), owl_similar(I,S,P,O,SP). owl_similar(0b00, S,P,O,SP) :- rdf_value(S,P,O,SP). owl_similar(0b10, S,P,O,SP) :- similar(S, S0), rdf_value(S0,P,O,SP). owl_similar(0b01, S,P,O,SP) :- similar(O, O0), rdf_value(S,P,O0,SP). owl_similar(0b11, S,P,O,SP) :- similar(S, S0), similar(O, O0), rdf_value(S0,P,O0,SP). %% owl_inv(?S, ?P, ?V, ?SP) % % As rdf_has/4 but include inverse properties owl_inv(S, P, O) :- owl_inv(S, P, O, _). owl_inv(S, P, O, SP) :- rdf_has(S, P, O, SP). owl_inv(S, P, O, SP) :- ground(P), !, inverse_predicate(P, IP), rdf_has(O, IP, S, SP). %% owl_same_inv(-S,-P,-V) % % As rdf_has/3 but include inverse properties owl_same_inv(S, P, O) :- owl_same_inv(S, P, O, _). owl_same_inv(S, P, O, Src) :- owl(S, P, O, Src). owl_same_inv(S, P, O, SP) :- ground(P), !, inverse_predicate(P, IP), owl(O, IP, S, SP). %% same(+R0, -R) is nondet. %% same(-R0, +R) is nondet. % % True if R is R0 or reachable through owl:sameAs relations. same(R0, R) :- atom(R0), !, empty_assoc(V0), put_assoc(R0, V0, true, V), same(R0, R, V). same(R0, R) :- atom(R), !, same(R, R0). same(R0, _R) :- instantiation_error(R0). same(R, R, _). same(R0, R, V) :- ( rdf_has(R0, owl:sameAs, R1) ; rdf_has(R1, owl:sameAs, R0) ), \+ get_assoc(R1, V, true), put_assoc(R1, V, true, V2), same(R1, R, V2). %% similar(+R0, -R) is nondet. % % True if R is R0 or reachable through owl:sameAs or % skos:exactMatch relations. similar(R0, R) :- empty_assoc(V0), put_assoc(R0, V0, true, V), similar(R0, R, V). similar(R, R, _). similar(R0, R, V) :- ( rdf_has(R0, owl:sameAs, R1) ; rdf_has(R1, owl:sameAs, R0) ; rdf_has(R0, skos:exactMatch, R1) ; rdf_has(R1, skos:exactMatch, R0) ), \+ get_assoc(R1, V, true), put_assoc(R1, V, true, V2), similar(R1, R, V2). %% inverse_predicate(+P1, +P2) is semidet. % % True if P1 and P2 are each others inverses. inverse_predicate(P1, P2) :- rdf_has(P1, owl:inverseOf, P2), !. inverse_predicate(P1, P2) :- rdf_has(P2, owl:inverseOf, P1), !. inverse_predicate(P, P) :- rdf(P, rdf:type, owl:'SymmetricProperty'). %% equivalence_set(+R, -Set) % % Set contains R and all its equivalent resources. equivalence_set(R, Set) :- findall(S, same(R, S), Set).