Daniel@0: /* Part of DML (Digital Music Laboratory) Daniel@0: Copyright 2014-2015 Samer Abdallah, University of London Daniel@0: Daniel@0: This program is free software; you can redistribute it and/or Daniel@0: modify it under the terms of the GNU General Public License Daniel@0: as published by the Free Software Foundation; either version 2 Daniel@0: of the License, or (at your option) any later version. Daniel@0: Daniel@0: This program is distributed in the hope that it will be useful, Daniel@0: but WITHOUT ANY WARRANTY; without even the implied warranty of Daniel@0: MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the Daniel@0: GNU General Public License for more details. Daniel@0: Daniel@0: You should have received a copy of the GNU General Public Daniel@0: License along with this library; if not, write to the Free Software Daniel@0: Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Daniel@0: */ Daniel@0: Daniel@0: :- module( dlogic, [ ext/2, lambda/3, unary/2 ]). Daniel@0: Daniel@0: :- use_module(library(semweb/rdf_db)). Daniel@0: :- use_module(library(semweb/rdfs)). Daniel@0: :- use_module(library(sandbox)). Daniel@0: :- use_module(library(rdfutils)). Daniel@0: Daniel@0: % :- meta_predicate unary(:,-). Daniel@0: :- meta_predicate lambda(-,0,-). Daniel@0: :- rdf_meta ext(t,o). Daniel@0: Daniel@0: :- op(400,xfx,~). Daniel@0: Daniel@0: ext((C1,C2),X) :- !, ext(C1,X), ext(C2,X). Daniel@0: ext(C1;C2, X) :- !, ext(C1,X); ext(C2,X). Daniel@0: ext(inv(P) is Q, X) :- !, rdf_has(V,P,X), call(Q,V). Daniel@0: ext(P is Q, X) :- !, rdf_has(X,P,V), call(Q,V). Daniel@0: ext(q(P,Q), X) :- !, rdf(X,P,literal(Q,_)). Daniel@0: ext(NS:Class,X) :- !, rdf_global_id(NS:Class,C), rdfs_individual_of(X,C). Daniel@0: ext(Class,X) :- atomic(Class), rdfs_individual_of(X,Class). Daniel@0: Daniel@0: lambda(X,Goal,Y) :- Daniel@0: copy_term(X-Goal,Y-Goal1), Daniel@0: call(Goal1). Daniel@0: Daniel@0: Daniel@0: unary((Binary -> Unary), X) :- !, binary(Binary,X,Y), unary(Unary,Y). Daniel@0: unary(\Pred,X) :- !, call(Pred,X). Daniel@0: unary((U1,U2),X) :- !, unary(U1,X), unary(U2,X). Daniel@0: unary((U1;U2),X) :- !, unary(U1,X); unary(U2,X). Daniel@0: unary(a(Class),X) :- !, rdf_global_id(Class,C), rdfs_individual_of(X,C). Daniel@0: unary(P~Q,X) :- !, rdf(X,P,literal(Q,_)). Daniel@0: Daniel@0: binary(p(P),X,Y) :- !, rdf_global_id(P,P1), rdf(X,P1,Y). Daniel@0: binary(ip(P),X,Y) :- !, rdf_global_id(P,P1), rdf(Y,P1,X). Daniel@0: binary(P~Q,X,Y) :- !, rdf_global_id(P,P1), rdf(X,P1,literal(Q,Y)). Daniel@0: binary(\Pred,X,Y) :- !, call(Pred,X,Y). Daniel@0: binary(text,X,Y) :- !, literal_text(X,Y). Daniel@0: binary(num,X,Y) :- !, literal_number(X,Y). Daniel@0: Daniel@0: Daniel@0: sandbox:safe_meta(dlogic:lambda(_,Goal,_),[Goal]). Daniel@0: