15:- module(utility_translation, [load_owl/1, load_owl_from_string/1, expand_all_ns/4, expand_all_ns/5, is_axiom/1]). 16 17:- dynamic trill_input_mode/1. 18 19:- use_module(library(lists),[member/2]). 20:- use_module(library(pengines)). 21 22:- use_module(library(sandbox)). 23 24:- discontiguous(valid_axiom/1). 25:- discontiguous(axiompred/1). 26:- discontiguous(axiom_arguments/2). 27:- discontiguous(expand_axiom/4). 28 29/***************************** 30 MESSAGES 31******************************/ 32:- multifile prolog:message/1. 33 34prologmessage(under_development) --> 35 [ 'NOTE: This function is under development. It may not work properly or may not work at all.' ]. 36 37 38 39builtin_class('http://www.w3.org/2002/07/owl#Thing'). 40builtin_class('http://www.w3.org/2002/07/owl#Nothing'). 41builtin_datatype('http://www.w3.org/2002/07/owl#real'). 42builtin_datatype('http://www.w3.org/2002/07/owl#rational'). 43builtin_datatype('http://www.w3.org/2001/XMLSchema#decimal'). 44builtin_datatype('http://www.w3.org/2001/XMLSchema#integer'). 45builtin_datatype('http://www.w3.org/2001/XMLSchema#nonNegativeInteger'). 46builtin_datatype('http://www.w3.org/2001/XMLSchema#nonPositiveInteger'). 47builtin_datatype('http://www.w3.org/2001/XMLSchema#positiveInteger'). 48builtin_datatype('http://www.w3.org/2001/XMLSchema#negativeInteger'). 49builtin_datatype('http://www.w3.org/2001/XMLSchema#long'). 50builtin_datatype('http://www.w3.org/2001/XMLSchema#int'). 51builtin_datatype('http://www.w3.org/2001/XMLSchema#short'). 52builtin_datatype('http://www.w3.org/2001/XMLSchema#byte'). 53builtin_datatype('http://www.w3.org/2001/XMLSchema#unsignedLong'). 54builtin_datatype('http://www.w3.org/2001/XMLSchema#unsignedInt'). 55builtin_datatype('http://www.w3.org/2001/XMLSchema#unsignedShort'). 56builtin_datatype('http://www.w3.org/2001/XMLSchema#unsignedByte'). 57builtin_datatype('http://www.w3.org/2001/XMLSchema#double'). 58builtin_datatype('http://www.w3.org/2001/XMLSchema#float'). 59builtin_datatype('http://www.w3.org/2001/XMLSchema#string'). 60builtin_datatype('http://www.w3.org/2001/XMLSchema#normalizedString'). 61builtin_datatype('http://www.w3.org/2001/XMLSchema#token'). 62builtin_datatype('http://www.w3.org/2001/XMLSchema#language'). 63builtin_datatype('http://www.w3.org/2001/XMLSchema#Name'). 64builtin_datatype('http://www.w3.org/2001/XMLSchema#NCName'). 65builtin_datatype('http://www.w3.org/2001/XMLSchema#NMTOKEN'). 66builtin_datatype('http://www.w3.org/2001/XMLSchema#boolean'). 67builtin_datatype('http://www.w3.org/2001/XMLSchema#hexBinary'). 68builtin_datatype('http://www.w3.org/2001/XMLSchema#base64Binary'). 69builtin_datatype('http://www.w3.org/2001/XMLSchema#minLength'). 70builtin_datatype('http://www.w3.org/2001/XMLSchema#maxLength'). 71builtin_datatype('http://www.w3.org/2001/XMLSchema#length'). 72builtin_datatype('http://www.w3.org/2001/XMLSchema#dateTime'). 73builtin_datatype('http://www.w3.org/2001/XMLSchema#dateTimeStamp'). 74builtin_datatype('http://www.w3.org/2000/01/rdf-schema#Literal'). 75 76is_class(C) :- get_module(M),M:class(C). 77is_class(C) :- builtin_class(C). 78 79/**************************************** 80 UTILITY 81 ****************************************/ 82set_trdf(Setting,Value):- 83 get_module(M), 84 retractall(M:trdf_setting(Setting,_)), 85 assert(M:trdf_setting(Setting,Value)). 86 87% TODO: hasKey 88 89/**************************************** 90 AXIOMS 91 ****************************************/
97:- meta_predicate entity( ). 98 99entity(M:A) :- individual(M:A). 100entity(M:A) :- property(M:A). 101entity(M:A) :- M:class(A). 102entity(M:A) :- M:datatype(A). 103axiom_arguments(entity,[iri]). 104valid_axiom(entity(A)) :- subsumed_by([A],[iri]). 105 106% declarationAxiom(M:individual(A)) :- individual(M:A). 107declarationAxiom(M:namedIndividual(A)) :- M:namedIndividual(A). 108declarationAxiom(M:objectProperty(A)) :- M:objectProperty(A). 109declarationAxiom(M:dataProperty(A)) :- M:dataProperty(A). 110declarationAxiom(M:annotationProperty(A)) :- M:annotationProperty(A). 111declarationAxiom(M:class(A)) :- M:class(A). 112declarationAxiom(M:datatype(A)) :- M:datatype(A). 113% TODO: check. here we treat the ontology declaration as an axiom; 114% this liberal definition of axiom allows us to iterate over axiom/1 115% to find every piece of information in the ontology. 116declarationAxiom(M:ontology(A)) :- M:ontology(A).
thread_local(class/1)
.122axiompred(class/1). 123axiom_arguments(class,[iri]). 124 125expand_class(M,C,NSList,ExpC) :- 126 expand_iri(M,C,NSList,ExpC), 127 \+ builtin_datatype(ExpC). 128 129valid_axiom(class(A)) :- subsumed_by([A],[iri]). 130expand_axiom(M,class(A),NSList,class(A_full_URL)) :- 131 expand_iri(M,A,NSList,A_full_URL), 132 ( M:addKBName -> add_kb_atoms(M,class,[A_full_URL]) ; true).
thread_local(datatype/1)
.138axiompred(datatype/1). 139axiom_arguments(datatype,[iri]). 140valid_axiom(datatype(A)) :- subsumed_by([A],[iri]). 141expand_axiom(M,datatype(A),NSList,datatype(A_full_URL)) :- 142 expand_iri(M,A,NSList,A_full_URL), 143 \+ name(A_full_URL,[95, 58, 68, 101, 115, 99, 114, 105, 112, 116, 105, 111, 110|_]), 144 ( M:addKBName -> add_kb_atoms(M,datatype,[A_full_URL]) ; true).
150:- meta_predicate property( ). 151 152property(M:A) :- M:dataProperty(A). 153property(M:A) :- M:objectProperty(A). 154property(M:A) :- M:annotationProperty(A). 155axiom_arguments(property,[iri]). 156valid_axiom(property(A)) :- subsumed_by([A],[iri]).
thread_local(objectProperty/1)
.162axiompred(objectProperty/1). 163axiom_arguments(objectProperty,[iri]). 164 165expand_objectProperty(M,P,NSList,ExpP) :- 166 expand_iri(M,P,NSList,ExpP), 167 ( M:addKBName -> add_kb_atoms(M,objectProperty,[ExpP]) ; true ). 168 169valid_axiom(objectProperty(A)) :- subsumed_by([A],[iri]). 170expand_axiom(M,objectProperty(A),NSList,objectProperty(A_full_URL)) :- 171 expand_iri(M,A,NSList,A_full_URL), 172 ( M:addKBName -> add_kb_atoms(M,objectProperty,[A_full_URL]) ; true).
thread_local(dataProperty/1)
.178axiompred(dataProperty/1). 179axiom_arguments(dataProperty,[iri]). 180 181expand_dataProperty(M,P,NSList,ExpP) :- 182 expand_iri(M,P,NSList,ExpP), 183 ( M:addKBName -> add_kb_atoms(M,dataProperty,[ExpP]) ; true). 184 185 186valid_axiom(dataProperty(A)) :- subsumed_by([A],[iri]). 187expand_axiom(M,dataProperty(A),NSList,dataProperty(A_full_URL)) :- 188 expand_iri(M,A,NSList,A_full_URL), 189 ( M:addKBName -> add_kb_atoms(M,dataProperty,[A_full_URL]) ; true).
thread_local(annotationProperty/1)
.195axiompred(annotationProperty/1). 196axiom_arguments(annotationProperty,[iri]). 197 198expand_annotationProperty(M,P,NSList,ExpP) :- 199 expand_iri(M,P,NSList,ExpP), 200 ( M:addKBName -> add_kb_atoms(M,annotationProperty,[ExpP]) ; true ). 201 202expand_annotationSubject(M,P,NSList,ExpP) :- 203 (expand_classExpression(M,P,NSList,ExpP),!) ; 204 (expand_individual(M,P,NSList,ExpP),!) ; 205 (expand_propertyExpression(M,P,NSList,ExpP),!) ; 206 (expand_axiom(M,P,NSList,ExpP),!). 207 208expand_annotationValue(M,P,NSList,ExpP) :- 209 (expand_literal(M,P,NSList,ExpP),!) ; 210 (expand_classExpression(M,P,NSList,ExpP),!) ; 211 (expand_individual(M,P,NSList,ExpP),!) ; 212 (expand_propertyExpression(M,P,NSList,ExpP),!) ; 213 (expand_axiom(M,P,NSList,ExpP),!) . 214 215 216valid_axiom(annotationProperty(A)) :- subsumed_by([A],[iri]). 217expand_axiom(M,annotationProperty(A),NSList,annotationProperty(A_full_URL)) :- 218 expand_iri(M,A,NSList,A_full_URL), 219 ( M:addKBName -> add_kb_atoms(M,annotationProperty,[A_full_URL]) ; true). 220 221expand_axiom(M,annotation(A,B,C),NSList,annotation(A_full_URL,B_full_URL,C_full_URL)) :- 222 ( M:addKBName -> (retractall(M:addKBName), Add=true) ; Add=false ), 223 expand_argument(M,A,NSList,A_full_URL), 224 expand_argument(M,B,NSList,B_full_URL), 225 expand_argument(M,C,NSList,C_full_URL), 226 ( Add=true -> assert(M:addKBName) ; true ).
232:- meta_predicate individual( ). 233 234individual(M:A) :- M:anonymousIndividual(A). 235individual(M:A) :- M:namedIndividual(A). 236%individual(A) :- nonvar(A),iri(A),\+property(A),\+class(A),\+ontology(A). % TODO: check: make individuals the default 237axiom_arguments(individual,[iri]). 238valid_axiom(individual(A)) :- subsumed_by([A],[iri]). 239 240expand_individuals(_M,[],_NSList,[]) :- !. 241expand_individuals(M,[H|T],NSList,[ExpH|ExpT]) :- 242 expand_individual(M,H,NSList,ExpH), 243 expand_individuals(M,T,NSList,ExpT). 244 245expand_individual(M,I,NSList,ExpI) :- 246 expand_iri(M,I,NSList,ExpI), 247 \+ builtin_datatype(ExpI), 248 ( M:addKBName -> add_kb_atoms(M,individual,[ExpI]) ; true ).
thread_local(namedIndividual/1)
.254axiompred(namedIndividual/1). 255axiom_arguments(namedIndividual,[iri]). 256valid_axiom(namedIndividual(A)) :- subsumed_by([A],[iri]). 257expand_axiom(M,namedIndividual(A),NSList,namedIndividual(A_full_URL)) :- 258 expand_iri(M,A,NSList,A_full_URL), 259 ( M:addKBName -> add_kb_atoms(M,individual,[A_full_URL]) ; true).
thread_local(anonymousIndividual/1)
.266axiompred(anonymousIndividual/1). 267axiom_arguments(anonymousIndividual,[iri]). 268valid_axiom(anonymousIndividual(A)) :- subsumed_by([A],[iri]). 269expand_axiom(M,anonymousIndividual(A),NSList,anonymousIndividual(A_full_URL)) :- 270 expand_iri(M,A,NSList,A_full_URL), 271 ( M:addKBName -> add_kb_atoms(M,individual,[A_full_URL]) ; true).
275:- meta_predicate costruct( ). 276 277construct(M:A) :- trill:axiom(M:A). 278construct(M:A) :- annotation(M:A). 279construct(M:A) :- M:ontology(A). 280axiom_arguments(construct,[iri]). 281valid_axiom(construct(A)) :- subsumed_by([A],[iri]).
286:- multifile trill:axiom/1. 287 288trillaxiom(M:A) :- classAxiom(M:A). 289trillaxiom(M:A) :- propertyAxiom(M:A). 290trillaxiom(M:hasKey(A,B)) :- M:hasKey(A,B). 291trillaxiom(M:A) :- fact(M:A). 292trillaxiom(M:A) :- declarationAxiom(M:A). 293%axiom(annotation(A,B,C)) :- 294% annotation(A,B,C). % CJM-treat annotations as axioms 295axiom_arguments(axiom,[axiom]). 296valid_axiom(axiom(A)) :- subsumed_by([A],[axiom]).
301:- meta_predicate classAxiom( ). 302 303classAxiom(M:equivalentClasses(A)) :- M:equivalentClasses(A). 304classAxiom(M:disjointClasses(A)) :- M:disjointClasses(A). 305classAxiom(M:subClassOf(A, B)) :- M:subClassOf(A, B). 306classAxiom(M:disjointUnion(A, B)) :- M:disjointUnion(A, B). 307axiom_arguments(classAxiom,[axiom]). 308valid_axiom(classAxiom(A)) :- subsumed_by([A],[axiom]).
317axiompred(subClassOf/2). 318axiom_arguments(subClassOf,[classExpression, classExpression]). 319valid_axiom(subClassOf(A, B)) :- subsumed_by([A, B],[classExpression, classExpression]). 320expand_axiom(M,subClassOf(A,B),NSList,subClassOf(A_full_URL,B_full_URL)) :- 321 expand_classExpression(M,A,NSList,A_full_URL), 322 expand_classExpression(M,B,NSList,B_full_URL).
thread_local(equivalentClasses/1)
.329axiompred(equivalentClasses/1). 330axiom_arguments(equivalentClasses,[set(classExpression)]). 331valid_axiom(equivalentClasses(A)) :- subsumed_by([A],[set(classExpression)]). 332expand_axiom(M,equivalentClasses(A),NSList,equivalentClasses(A_full_URL)) :- 333 expand_classExpressions(M,A,NSList,A_full_URL).
thread_local(disjointClasses/1)
.339axiompred(disjointClasses/1). 340axiom_arguments(disjointClasses,[set(classExpression)]). 341valid_axiom(disjointClasses(A)) :- subsumed_by([A],[set(classExpression)]). 342expand_axiom(M,disjointClasses(A),NSList,disjointClasses(A_full_URL)) :- 343 expand_classExpressions(M,A,NSList,A_full_URL).
thread_local(disjointUnion/2)
.349axiompred(disjointUnion/2). 350axiom_arguments(disjointUnion,[classExpression,set(classExpression)]). 351valid_axiom(disjointUnion(A,B)) :- subsumed_by([A,B],[classExpression,set(classExpression)]). 352expand_axiom(M,disjointUnion(A,B),NSList,disjointUnion(A_full_URL,B_full_URL)) :- 353 expand_classExpression(M,A,NSList,A_full_URL), 354 expand_classExpressions(M,B,NSList,B_full_URL).
360:- meta_predicate propertyAxiom( ). 361 362propertyAxiom(M:symmetricProperty(A)) :- M:symmetricProperty(A). 363propertyAxiom(M:inverseFunctionalProperty(A)) :- M:inverseFunctionalProperty(A). 364propertyAxiom(M:transitiveProperty(A)) :- M:transitiveProperty(A). 365propertyAxiom(M:asymmetricProperty(A)) :- M:asymmetricProperty(A). 366propertyAxiom(M:subPropertyOf(A, B)) :- M:subPropertyOf(A, B). 367propertyAxiom(M:functionalProperty(A)) :- M:functionalProperty(A). 368propertyAxiom(M:irreflexiveProperty(A)) :- M:irreflexiveProperty(A). 369propertyAxiom(M:disjointProperties(A)) :- M:disjointProperties(A). 370propertyAxiom(M:propertyDomain(A, B)) :- M:propertyDomain(A, B). 371propertyAxiom(M:reflexiveProperty(A)) :- M:reflexiveProperty(A). 372propertyAxiom(M:propertyRange(A, B)) :- M:propertyRange(A, B). 373propertyAxiom(M:equivalentProperties(A)) :- M:equivalentProperties(A). 374propertyAxiom(M:inverseProperties(A, B)) :- M:inverseProperties(A, B). 375axiom_arguments(propertyAxiom,[axiom]). 376valid_axiom(propertyAxiom(A)) :- subsumed_by([A],[axiom]).
thread_local(subPropertyOf/2)
.384axiompred(subPropertyOf/2). 385axiom_arguments(subPropertyOf,[propertyExpression, objectPropertyExpression]). 386valid_axiom(subPropertyOf(A, B)) :- subsumed_by([A, B],[propertyExpression, objectPropertyExpression]). 387%expand_axiom(M,subPropertyOf(A,B),NSList,subPropertyOf(A_full_URL,B_full_URL)) :- %TODO: fix for data properties 388% expand_propertyExpression(M,A,NSList,A_full_URL), 389% expand_objectPropertyExpression(M,B,NSList,B_full_URL).
393subObjectPropertyOf(A, B) :- get_module(M),M:subPropertyOf(A, B),subsumed_by([A, B],[objectPropertyExpressionOrChain, objectPropertyExpression]). 394axiom_arguments(subObjectPropertyOf,[objectPropertyExpressionOrChain, objectPropertyExpression]). 395valid_axiom(subObjectPropertyOf(A, B)) :- subsumed_by([A, B],[objectPropertyExpressionOrChain, objectPropertyExpression]). 396expand_axiom(M,subPropertyOf(A,B),NSList,subPropertyOf(A_full_URL,B_full_URL)) :- 397 expand_objectPropertyExpressionOrChain(M,A,NSList,A_full_URL), 398 expand_objectPropertyExpression(M,B,NSList,B_full_URL). 399 %add_expressivity(M,h).
403subDataPropertyOf(A, B) :- get_module(M),M:subPropertyOf(A, B),subsumed_by([A, B],[dataPropertyExpression, dataPropertyExpression]). 404axiom_arguments(subDataPropertyOf,[dataPropertyExpression, dataPropertyExpression]). 405valid_axiom(subDataPropertyOf(A, B)) :- subsumed_by([A, B],[dataPropertyExpression, dataPropertyExpression]).
409subAnnotationPropertyOf(A, B) :- get_module(M),M:subPropertyOf(A, B),subsumed_by([A, B],[annotationProperty, annotationProperty]). 410axiom_arguments(subAnnotationPropertyOf,[annotationProperty, annotationProperty]). 411valid_axiom(subAnnotationPropertyOf(A, B)) :- subsumed_by([A, B],[annotationProperty, annotationProperty]).
thread_local(equivalentProperties/1)
.418axiompred(equivalentProperties/1). 419axiom_arguments(equivalentProperties,[set(propertyExpression)]). 420valid_axiom(equivalentProperties(A)) :- subsumed_by([A],[set(propertyExpression)]). 421expand_axiom(M,equivalentProperties(A),NSList,equivalentProperties(A_full_URL)) :- 422 expand_propertyExpressions(M,A,NSList,A_full_URL).
426equivalentObjectProperties(A) :- get_module(M),M:equivalentProperties(A),subsumed_by([A],[set(objectPropertyExpression)]). 427axiom_arguments(equivalentObjectProperties,[set(objectPropertyExpression)]). 428valid_axiom(equivalentObjectProperties(A)) :- subsumed_by([A],[set(objectPropertyExpression)]).
432equivalentDataProperties(A) :- get_module(M),M:equivalentProperties(A),subsumed_by([A],[set(dataPropertyExpression)]). 433axiom_arguments(equivalentDataProperties,[set(dataPropertyExpression)]). 434valid_axiom(equivalentDataProperties(A)) :- subsumed_by([A],[set(dataPropertyExpression)]).
thread_local(disjointProperties/1)
.441axiompred(disjointProperties/1). 442axiom_arguments(disjointProperties,[set(propertyExpression)]). 443valid_axiom(disjointProperties(A)) :- subsumed_by([A],[set(propertyExpression)]). 444expand_axiom(M,disjointProperties(A),NSList,disjointProperties(A_full_URL)) :- 445 expand_propertyExpressions(M,A,NSList,A_full_URL).
449disjointObjectProperties(A) :- get_module(M),M:disjointProperties(A),subsumed_by([A],[set(objectPropertyExpression)]). 450axiom_arguments(disjointObjectProperties,[set(objectPropertyExpression)]). 451valid_axiom(disjointObjectProperties(A)) :- subsumed_by([A],[set(objectPropertyExpression)]).
455disjointDataProperties(A) :- get_module(M),M:disjointProperties(A),subsumed_by([A],[set(dataPropertyExpression)]). 456axiom_arguments(disjointDataProperties,[set(dataPropertyExpression)]). 457valid_axiom(disjointDataProperties(A)) :- subsumed_by([A],[set(dataPropertyExpression)]).
inverseProperties(partOf,hasPart)
(extensional predicate - can be asserted)
:- thread_local(inverseProperties/2)
.467axiompred(inverseProperties/2). 468axiom_arguments(inverseProperties,[objectPropertyExpression, objectPropertyExpression]). 469valid_axiom(inverseProperties(A, B)) :- subsumed_by([A, B],[objectPropertyExpression, objectPropertyExpression]). 470expand_axiom(M,inverseProperties(A,B),NSList,inverseProperties(A_full_URL,B_full_URL)) :- 471 expand_objectPropertyExpression(M,A,NSList,A_full_URL), 472 expand_objectPropertyExpression(M,B,NSList,B_full_URL). 473 %add_expressivity(M,i).
480%:- thread_local(propertyDomain/2). 481 482axiompred(propertyDomain/2). 483axiom_arguments(propertyDomain,[propertyExpression, classExpression]). 484valid_axiom(propertyDomain(A, B)) :- subsumed_by([A, B],[propertyExpression, classExpression]). 485expand_axiom(M,propertyDomain(A,B),NSList,propertyDomain(A_full_URL,B_full_URL)) :- 486 expand_propertyExpression(M,A,NSList,A_full_URL), 487 expand_classExpression(M,B,NSList,B_full_URL).
491objectPropertyDomain(A, B) :- get_module(M),M:propertyDomain(A, B),subsumed_by([A, B],[objectPropertyExpression, classExpression]). 492axiom_arguments(objectPropertyDomain,[objectPropertyExpression, classExpression]). 493valid_axiom(objectPropertyDomain(A, B)) :- subsumed_by([A, B],[objectPropertyExpression, classExpression]).
497dataPropertyDomain(A, B) :- get_module(M),M:propertyDomain(A, B),subsumed_by([A, B],[dataPropertyExpression, classExpression]). 498axiom_arguments(dataPropertyDomain,[dataPropertyExpression, classExpression]). 499valid_axiom(dataPropertyDomain(A, B)) :- subsumed_by([A, B],[dataPropertyExpression, classExpression]).
503annotationPropertyDomain(A, B) :- get_module(M),M:propertyDomain(A, B),subsumed_by([A, B],[annotationProperty, iri]). 504axiom_arguments(annotationPropertyDomain,[annotationProperty, iri]). 505valid_axiom(annotationPropertyDomain(A, B)) :- subsumed_by([A, B],[annotationProperty, iri]).
thread_local(propertyRange/2)
.512axiompred(propertyRange/2). 513axiom_arguments(propertyRange,[propertyExpression, classExpression]). 514valid_axiom(propertyRange(A, B)) :- subsumed_by([A, B],[propertyExpression, classExpression]). 515expand_axiom(M,propertyRange(A,B),NSList,propertyRange(A_full_URL,B_full_URL)) :- 516 expand_iri(M,B,NSList,Datatype), 517 builtin_datatype(Datatype),!, 518 expand_dataRange(M,B,NSList,B_full_URL), 519 expand_dataPropertyExpression(M,A,NSList,A_full_URL). 520expand_axiom(M,propertyRange(A,B),NSList,propertyRange(A_full_URL,B_full_URL)) :- 521 expand_propertyExpression(M,A,NSList,A_full_URL), 522 expand_classExpression(M,B,NSList,B_full_URL).
526objectPropertyRange(A, B) :- propertyRange(A, B),subsumed_by([A, B],[objectPropertyExpression, classExpression]). 527axiom_arguments(objectPropertyRange,[objectPropertyExpression, classExpression]). 528valid_axiom(objectPropertyRange(A, B)) :- subsumed_by([A, B],[objectPropertyExpression, classExpression]).
532dataPropertyRange(A, B) :- get_module(M),M:propertyRange(A, B),subsumed_by([A, B],[dataPropertyExpression, dataRange]). 533axiom_arguments(dataPropertyRange,[objectPropertyExpression, dataRange]). 534valid_axiom(dataPropertyRange(A, B)) :- subsumed_by([A, B],[objectPropertyExpression, dataRange]).
538annotationPropertyRange(A, B) :- get_module(M),M:propertyRange(A, B),subsumed_by([A, B],[annotationProperty, iri]). 539axiom_arguments(annotationPropertyRange,[annotationProperty, iri]). 540valid_axiom(annotationPropertyRange(A, B)) :- subsumed_by([A, B],[annotationProperty, iri]).
thread_local(functionalProperty/1)
.547axiompred(functionalProperty/1). 548axiom_arguments(functionalProperty,[propertyExpression]). 549valid_axiom(functionalProperty(A)) :- subsumed_by([A],[propertyExpression]). 550expand_axiom(M,functionalProperty(A),NSList,functionalProperty(A_full_URL)) :- 551 expand_propertyExpression(M,A,NSList,A_full_URL). 552 %add_expressivity(M,f).
556functionalObjectProperty(A) :- get_module(M),M:functionalProperty(A),subsumed_by([A],[objectPropertyExpression]). 557axiom_arguments(functionalObjectProperty,[objectPropertyExpression]). 558valid_axiom(functionalObjectProperty(A)) :- subsumed_by([A],[objectPropertyExpression]).
562functionalDataProperty(A) :- get_module(M),M:functionalProperty(A),subsumed_by([A],[dataPropertyExpression]). 563axiom_arguments(functionalDataProperty,[dataPropertyExpression]). 564valid_axiom(functionalDataProperty(A)) :- subsumed_by([A],[dataPropertyExpression]).
thread_local(inverseFunctionalProperty/1)
.570axiompred(inverseFunctionalProperty/1). 571axiom_arguments(inverseFunctionalProperty,[objectPropertyExpression]). 572valid_axiom(inverseFunctionalProperty(A)) :- subsumed_by([A],[objectPropertyExpression]). 573expand_axiom(M,inverseFunctionalProperty(A),NSList,inverseFunctionalProperty(A_full_URL)) :- 574 expand_objectPropertyExpression(M,A,NSList,A_full_URL). 575 %add_expressivity(M,i), 576 %add_expressivity(M,f).
thread_local(reflexiveProperty/1)
.582axiompred(reflexiveProperty/1). 583axiom_arguments(reflexiveProperty,[objectPropertyExpression]). 584valid_axiom(reflexiveProperty(A)) :- subsumed_by([A],[objectPropertyExpression]). 585expand_axiom(M,reflexiveProperty(A),NSList,reflexiveProperty(A_full_URL)) :- 586 expand_objectPropertyExpression(M,A,NSList,A_full_URL).
thread_local(irreflexiveProperty/1)
.592axiompred(irreflexiveProperty/1). 593axiom_arguments(irreflexiveProperty,[objectPropertyExpression]). 594valid_axiom(irreflexiveProperty(A)) :- subsumed_by([A],[objectPropertyExpression]). 595expand_axiom(M,irreflexiveProperty(A),NSList,irreflexiveProperty(A_full_URL)) :- 596 expand_objectPropertyExpression(M,A,NSList,A_full_URL).
thread_local(symmetricProperty/1)
.602axiompred(symmetricProperty/1). 603axiom_arguments(symmetricProperty,[objectPropertyExpression]). 604valid_axiom(symmetricProperty(A)) :- subsumed_by([A],[objectPropertyExpression]). 605expand_axiom(M,symmetricProperty(A),NSList,symmetricProperty(A_full_URL)) :- 606 expand_objectPropertyExpression(M,A,NSList,A_full_URL).
thread_local(asymmetricProperty/1)
.612axiompred(asymmetricProperty/1). 613axiom_arguments(asymmetricProperty,[objectPropertyExpression]). 614valid_axiom(asymmetricProperty(A)) :- subsumed_by([A],[objectPropertyExpression]). 615expand_axiom(M,asymmetricProperty(A),NSList,asymmetricProperty(A_full_URL)) :- 616 expand_objectPropertyExpression(M,A,NSList,A_full_URL).
thread_local(transitiveProperty/1)
.622axiompred(transitiveProperty/1). 623axiom_arguments(transitiveProperty,[objectPropertyExpression]). 624valid_axiom(transitiveProperty(A)) :- subsumed_by([A],[objectPropertyExpression]). 625expand_axiom(M,transitiveProperty(A),NSList,transitiveProperty(A_full_URL)) :- 626 expand_objectPropertyExpression(M,A,NSList,A_full_URL). 627 %add_rule(M,forall_plus_rule), 628 %add_expressivity(M,s).
thread_local(hasKey/2)
.634axiompred(hasKey/2). 635axiom_arguments(hasKey,[classExpression,propertyExpression]). 636valid_axiom(hasKey(CE,PE)) :- subsumed_by([CE,PE],[classExpression,propertyExpression]). 637expand_axiom(M,hasKey(A,B),NSList,hasKey(A_full_URL,B_full_URL)) :- 638 expand_classExpression(M,A,NSList,A_full_URL), 639 expand_propertyExpression(M,B,NSList,B_full_URL).
646:- meta_predicate fact( ). 647 648fact(M:annotationAssertion(A, B, C)) :- M:annotationAssertion(A, B, C). 649fact(M:differentIndividuals(A)) :- M:differentIndividuals(A). 650fact(M:negativePropertyAssertion(A, B, C)) :- M:negativePropertyAssertion(A, B, C). 651fact(M:propertyAssertion(A, B, C)) :- M:propertyAssertion(A, B, C). 652fact(M:sameIndividual(A)) :- M:sameIndividual(A). 653fact(M:classAssertion(A, B)) :- M:classAssertion(A, B). 654axiom_arguments(fact,[axiom]). 655valid_axiom(fact(A)) :- subsumed_by([A],[axiom]).
thread_local(sameIndividual/1)
.662axiompred(sameIndividual/1). 663axiom_arguments(sameIndividual,[set(individual)]). 664valid_axiom(sameIndividual(A)) :- subsumed_by([A],[set(individual)]). 665expand_axiom(M,sameIndividual(A),NSList,sameIndividual(A_full_URL)) :- 666 expand_individuals(M,A,NSList,A_full_URL).
thread_local(differentIndividuals/1)
.672axiompred(differentIndividuals/1). 673axiom_arguments(differentIndividuals,[set(individual)]). 674valid_axiom(differentIndividuals(A)) :- subsumed_by([A],[set(individual)]). 675expand_axiom(M,differentIndividuals(A),NSList,differentIndividuals(A_full_URL)) :- 676 expand_individuals(M,A,NSList,A_full_URL).
thread_local(classAssertion/2)
.682axiompred(classAssertion/2). 683axiom_arguments(classAssertion,[classExpression, individual]). 684valid_axiom(classAssertion(A, B)) :- subsumed_by([A, B],[classExpression, individual]). 685expand_axiom(M,classAssertion(A,B),NSList,B_full_URL) :- 686 expand_iri(M,A,NSList,'http://www.w3.org/2000/01/rdf-schema#Datatype'),!, 687 ( expand_axiom(M,datatype(B),NSList,B_full_URL) -> true ; B_full_URL='none' ). 688expand_axiom(M,classAssertion(A,B),NSList,classAssertion(A_full_URL,B_full_URL)) :- 689 expand_classExpression(M,A,NSList,A_full_URL), 690 expand_individual(M,B,NSList,B_full_URL).
thread_local(propertyAssertion/3)
.697axiompred(propertyAssertion/3). 698axiom_arguments(propertyAssertion,[propertyExpression, individual, individual]). 699valid_axiom(propertyAssertion(A, B, C)) :- subsumed_by([A, B, C],[propertyExpression, individual, individual]). 700expand_axiom(M,propertyAssertion(A,B,C),NSList,propertyAssertion(IRI,B_full_URL,C_full_URL)) :- 701 expand_iri(M,A,NSList,IRI), 702 ( IRI='http://www.w3.org/2000/01/rdf-schema#label' ; IRI='http://www.w3.org/2000/01/rdf-schema#comment' ),!, 703 expand_iri(M,B,NSList,B_full_URL), 704 ( expand_iri(M,C,NSList,C_full_URL) ; expand_literal(M,C,NSList,C_full_URL) ), !. 705expand_axiom(M,propertyAssertion(A,B,C),NSList,propertyAssertion(A_full_URL,B_full_URL,C_full_URL)) :- 706 expand_individual(M,C,NSList,C_full_URL),!, 707 expand_individual(M,B,NSList,B_full_URL), 708 expand_objectPropertyExpression(M,A,NSList,A_full_URL). 709expand_axiom(M,propertyAssertion(A,B,C),NSList,propertyAssertion(A_full_URL,B_full_URL,C_full_URL)) :- 710 expand_literal(M,C,NSList,C_full_URL), 711 expand_individual(M,B,NSList,B_full_URL), 712 expand_dataPropertyExpression(M,A,NSList,A_full_URL).
717objectPropertyAssertion(A, B, C) :- get_module(M),M:propertyAssertion(A, B, C),subsumed_by([A, B, C],[objectPropertyExpression, individual, individual]). 718axiom_arguments(objectPropertyAssertion,[objectPropertyExpression, individual, individual]). 719valid_axiom(objectPropertyAssertion(A, B, C)) :- subsumed_by([A, B, C],[objectPropertyExpression, individual, individual]).
723dataPropertyAssertion(A, B, C) :- get_module(M),M:propertyAssertion(A, B, C),subsumed_by([A, B, C],[dataPropertyExpression, individual, literal]). 724axiom_arguments(dataPropertyAssertion,[objectPropertyExpression, individual, literal]). 725valid_axiom(dataPropertyAssertion(A, B, C)) :- subsumed_by([A, B, C],[dataPropertyExpression, individual, literal]).
thread_local(negativePropertyAssertion/3)
.732axiompred(negativePropertyAssertion/3). 733axiom_arguments(negativePropertyAssertion,[propertyExpression, individual, individual]). 734valid_axiom(negativePropertyAssertion(A, B, C)) :- subsumed_by([A, B, C],[propertyExpression, individual, individual]). 735expand_axiom(M,negativePropertyAssertion(A,B,C),NSList,negativePropertyAssertion(A_full_URL,B_full_URL,C_full_URL)) :- 736 expand_individual(M,C,NSList,C_full_URL),!, 737 expand_individual(M,B,NSList,B_full_URL), 738 expand_objectPropertyExpression(M,A,NSList,A_full_URL). 739expand_axiom(M,negativePropertyAssertion(A,B,C),NSList,negativePropertyAssertion(A_full_URL,B_full_URL,C_full_URL)) :- 740 expand_literal(M,C,NSList,C_full_URL), 741 expand_individual(M,B,NSList,B_full_URL), 742 expand_dataPropertyExpression(M,A,NSList,A_full_URL).
746negativeObjectPropertyAssertion(A, B, C) :- get_module(M),M:negativePropertyAssertion(A, B, C),subsumed_by([A, B, C],[objectPropertyExpression, individual, individual]). 747axiom_arguments(negativeObjectPropertyAssertion,[objectPropertyExpression, individual, individual]). 748valid_axiom(negativeObjectPropertyAssertion(A, B, C)) :- subsumed_by([A, B, C],[objectPropertyExpression, individual, individual]).
752negativeDataPropertyAssertion(A, B, C) :- get_module(M),M:negativePropertyAssertion(A, B, C),subsumed_by([A, B, C],[dataPropertyExpression, individual, literal]). 753axiom_arguments(negativeDataPropertyAssertion,[dataPropertyExpression, individual, literal]). 754valid_axiom(negativeDataPropertyAssertion(A, B, C)) :- subsumed_by([A, B, C],[dataPropertyExpression, individual, literal]).
thread_local(annotationAssertion/3)
.760axiompred(annotationAssertion/3). 761axiom_arguments(annotationAssertion,[annotationProperty, annotationSubject, annotationValue]). 762valid_axiom(annotationAssertion(A, B, C)) :- subsumed_by([A, B, C],[annotationProperty, annotationSubject, annotationValue]). 763annotationSubject(_). 764annotationValue(_). 765expand_axiom(M,annotationAssertion(A,B,C),NSList,annotationAssertion(A_full_URL,B_full_URL,C_full_URL)) :- 766 expand_annotationProperty(M,A,NSList,A_full_URL), 767 expand_annotationSubject(M,B,NSList,B_full_URL), 768 expand_annotationValue(M,C,NSList,C_full_URL).
775axiompred(annotation/3). 776 777annotation(M:annotationAnnotation(A, B, C)) :- M:annotationAnnotation(M:A, B, C). 778annotation(M:axiomAnnotation(A, B, C)) :- M:axiomAnnotation(M:A, B, C). 779axiom_arguments(annotation,[iri,annotationProperty,annotationValue]). 780valid_axiom(annotation(A,B,C)) :- subsumed_by([A,B,C],[iri,annotationProperty,annotationValue]). 781expand_axiom(M,annotationAnnotation(A,B,C),NSList,annotationAnnotation(A_full_URL,B_full_URL,C_full_URL)) :- 782 expand_iri(M,A,NSList,A_full_URL), 783 expand_annotationProperty(M,B,NSList,B_full_URL), 784 expand_annotationValue(M,C,NSList,C_full_URL), 785 ( M:addKBName -> add_kb_atoms(M,annotationProperty,[A_full_URL]) ; true ).
788ontologyAnnotation(M:Ontology,AP,AV) :- 789 M:annotation(Ontology,AP,AV), 790 M:ontology(Ontology). 791axiom_arguments(ontologyAnnotation,[ontology, annotationProperty, annotationValue]). 792valid_axiom(ontologyAnnotation(A, B, C)) :- subsumed_by([A, B, C],[ontology, annotationProperty, annotationValue]).
795axiomAnnotation(M:Axiom,AP,AV) :- 796 M:annotation(Axiom,AP,AV), 797 M:axiom(Axiom). 798axiom_arguments(axiomAnnotation,[axiom, annotationProperty, annotationValue]). 799valid_axiom(axiomAnnotation(A, B, C)) :- subsumed_by([A, B, C],[axiom, annotationProperty, annotationValue]).
802annotationAnnotation(M:Annotation,AP,AV) :- 803 M:annotation(Annotation,AP,AV), 804 annotation(M:Annotation). 805axiom_arguments(annotationAnnotation,[annotation, annotationProperty, annotationValue]). 806valid_axiom(annotationAnnotation(A, B, C)) :- subsumed_by([A, B, C],[annotation, annotationProperty, annotationValue]).
thread_local(ontology/1)
.812expand_ontology(M,A,NSList,A_full_URL) :- 813 expand_iri(M,A,NSList,A_full_URL). 814 815axiompred(ontology/1). 816axiom_arguments(ontology,[iri]). 817valid_axiom(ontology(A)) :- subsumed_by([A],[iri]). 818expand_axiom(M,ontology(A),NSList,ontology(A_full_URL)) :- 819 expand_iri(M,A,NSList,A_full_URL).
823:- meta_predicate ontologyDirective( , ). 824 825ontologyDirective(M:A, B) :- M:ontologyImport(A, B). 826ontologyDirective(M:A, B) :- M:ontologyAxiom(A, B). 827ontologyDirective(M:A, B) :- M:ontologyVersionInfo(A, B). 828axiom_arguments(ontologyDirective,[ontology, iri]). 829valid_axiom(ontologyDirective(A, B)) :- subsumed_by([A, B],[ontology, iri]).
subClassOf('http://example.org#a', 'http://example.org#b'). ontologyAxiom('http://example.org#', subClassOf('http://example.org#a','http://example.org#b')).
:- thread_local(ontologyAxiom/2)
.
841axiompred(ontologyAxiom/2). 842axiom_arguments(ontologyAxiom,[ontology, axiom]). 843valid_axiom(ontologyAxiom(A, B)) :- subsumed_by([A, B],[ontology, axiom]). 844expand_axiom(M,ontologyAxiom(A,B),NSList,ontology(A_full_URL,B_full_URL)) :- 845 expand_ontology(M,A,NSList,A_full_URL), 846 expand_axiom(M,B,NSList,B_full_URL).
thread_local(ontologyImport/2)
.852axiompred(ontologyImport/2). 853axiom_arguments(ontologyImport,[ontology, iri]). 854valid_axiom(ontologyImport(A, B)) :- subsumed_by([A, B],[ontology, iri]). 855expand_axiom(M,ontologyImport(A,B),NSList,ontology(A_full_URL,B)) :- 856 expand_iri(M,A,NSList,A_full_URL), 857 M:consult(B).
thread_local(ontologyVersionInfo/2)
.862axiompred(ontologyVersionInfo/2). 863axiom_arguments(ontologyVersionInfo,[ontology, iri]). 864valid_axiom(ontologyVersionInfo(A, B)) :- subsumed_by([A, B],[ontology, iri]). 865 866/**************************************** 867 RESTRICTIONS ON AXIOMS 868 ****************************************/ 869 870% 11.1 871% An object property expression OPE is simple in Ax if, for each object property expression OPE' such that OPE' ->* OPE holds, OPE' is not composite. 872% (The property hierarchy relation ->* is the reflexive-transitive closure of ->) 873%simpleObjectPropertyExpresion(OPE) :- 874% objectPropertyExpression(OPE), 875 876 877/**************************************** 878 EXPRESSIONS 879 ****************************************/ 880 881subsumed_by(X,_) :- var(X),!. 882subsumed_by([],[]) :- !. 883subsumed_by([I|IL],[T|TL]) :- 884 !, 885 subsumed_by(I,T), 886 subsumed_by(IL,TL). 887subsumed_by(L,set(T)):- 888 !, 889 forall(member(I,L), 890 subsumed_by(I,T)). 891subsumed_by(I,T):- 892 !, 893 G=..[T,I], 894 get_module(M), 895 M:G.
TODO
: currently underconstrained, any atomic term can be an IRI900iri(IRI) :- atomic(IRI). % 901expand_iri(_M,NS_URL,NSList,Full_URL):- 902 atomic(NS_URL), 903 NS_URL \= literal(_), 904 uri_split(NS_URL,Short_NS,Term, ':'), 905 member((Short_NS=Long_NS),NSList), 906 concat_atom([Long_NS,Term],Full_URL),!. 907 908expand_iri(_M,NS_URL,NSList,Full_URL):- 909 atomic(NS_URL), 910 NS_URL \= literal(_), 911 \+ sub_atom(NS_URL,_,_,_,':'), 912 member(([]=Long_NS),NSList), 913 concat_atom([Long_NS,NS_URL],Full_URL),!. 914 915expand_iri(_M,IRI,_NSList,IRI):- atomic(IRI).
literal(_)
. % TODO
921literal(literal(_)). % TODO 922expand_literal(M,literal(type(Type,Val)),NSList,literal(type(ExpType,Val))) :- 923 expand_datatype(M,Type,NSList,ExpType),!. 924expand_literal(_M,literal(Literal),_NSList,literal(Literal)). 925 926propertyExpression(E) :- objectPropertyExpression(E) ; dataPropertyExpression(E). 927 928expand_propertyExpressions(_M,[],_NSList,[]) :- !. 929expand_propertyExpressions(M,[CE|T],NSList,[ExpCE|ExpT]) :- 930 expand_propertyExpression(M,CE,NSList,ExpCE), 931 expand_propertyExpressions(M,T,NSList,ExpT). 932 933% expand_propertyExpression(M,E,NSList,ExpE):- expand_objectPropertyExpression(M,E,NSList,ExpE) ; expand_dataPropertyExpression(M,E,NSList,ExpE). % TODO: support for datatype to implement 934expand_propertyExpression(M,inverseOf(OP),NSList,inverseOf(ExpOP)) :- !, 935 expand_objectProperty(M,OP,NSList,ExpOP). 936 %add_expressivity(M,i). 937expand_propertyExpression(M,E,NSList,ExpE) :- expand_objectProperty(M,E,NSList,ExpE).
942objectPropertyExpression(E) :- objectProperty(E) ; inverseObjectProperty(E). 943% expand_objectPropertyExpression(M,E,NSList,ExpE) :- expand_objectProperty(M,E,NSList,ExpE) ; expand_inverseObjectProperty(M,E,NSList,ExpE). 944expand_objectPropertyExpression(M,inverseOf(OP),NSList,inverseOf(ExpOP)) :- !,expand_objectProperty(M,OP,NSList,ExpOP). 945 %add_expressivity(M,i). 946expand_objectPropertyExpression(M,E,NSList,ExpE) :- expand_objectProperty(M,E,NSList,ExpE). 947 948% give benefit of doubt; e.g. rdfs:label 949% in the OWL2 spec we have DataProperty := IRI 950% here dataProperty/1 is an asserted fact 951objectPropertyExpression(E) :- nonvar(E),iri(E). 952 953objectPropertyExpressionOrChain(propertyChain(PL)) :- forall(member(P,PL),objectPropertyExpression(P)). 954objectPropertyExpressionOrChain(PE) :- objectPropertyExpression(PE). 955expand_objectPropertyExpressionOrChain(M,propertyChain(PL),NSList,propertyChain(ExpPL)):- !, 956 expand_propertyExpressions(M,PL,NSList,ExpPL). 957 %add_expressivity(M,r). 958expand_objectPropertyExpressionOrChain(M,P,NSList,ExpP):- 959 expand_objectPropertyExpression(M,P,NSList,ExpP). 960 961 962 963inverseObjectProperty(inverseOf(OP)) :- objectProperty(OP). 964expand_inverseObjectProperty(M,inverseOf(OP),NSList,inverseOf(ExpOP)) :- expand_objectProperty(M,OP,NSList,ExpOP). 965 %add_expressivity(M,i). 966 967expand_dataPropertyExpressions(M,DPEs,NSList,ExpDPEs) :- expand_dataPropertyExpression(M,DPEs,NSList,ExpDPEs). 968 969dataPropertyExpression(E) :- dataProperty(E). 970expand_dataPropertyExpression(M,E,NSList,ExpE) :- expand_dataProperty(M,E,NSList,ExpE). 971 972dataPropertyExpression(DPEs) :- 973 ( is_list(DPEs) 974 -> forall(member(DPE,DPEs), 975 dataPropertyExpression(DPE)) 976 ; dataPropertyExpression(DPEs)). 977 978expand_dataPropertyExpression(_M,[],_NSList,[]) :- !. 979expand_dataPropertyExpression(M,[DPE|T],NSList,[ExpDPE|ExpT]) :- 980 expand_dataPropertyExpression(M,DPE,NSList,ExpDPE), 981 expand_dataPropertyExpression(M,T,NSList,ExpT). 982 983% give benefit of doubt; e.g. rdfs:label 984% in the OWL2 spec we have DataProperty := IRI 985% here dataProperty/1 is an asserted fact 986dataPropertyExpression(E) :- nonvar(E),iri(E). 987 988%already declared as entity 989%datatype(IRI) :- iri(IRI). 990expand_datatype(M,DT,NSList,ExpDT) :- 991 expand_iri(M,DT,NSList,ExpDT), 992 builtin_datatype(ExpDT). 993 994expand_dataRanges(_M,[],_NSList,[]) :- !. 995expand_dataRanges(M,[H|T],NSList,[ExpH|ExpT]) :- 996 expand_dataRange(M,H,NSList,ExpH), 997 expand_dataRanges(M,T,NSList,ExpT).
1000dataRange(DR) :- 1001 (datatype(DR) ; 1002 dataIntersectionOf(DR ); 1003 dataUnionOf(DR) ; 1004 dataComplementOf(DR) ; 1005 dataOneOf(DR) ; 1006 datatypeRestriction(DR)),!. 1007expand_dataRange(M,intersectionOf(DRs),NSList,intersectionOf(ExpDRs)) :- !, 1008 expand_dataRanges(M,DRs,NSList,ExpDRs). 1009expand_dataRange(M,unionOf(DRs),NSList,unionOf(ExpDRs)) :- !, 1010 expand_dataRanges(M,DRs,NSList,ExpDRs). 1011expand_dataRange(M,complementOf(DR),NSList,complementOf(ExpDR)) :- !, 1012 expand_dataRange(M,DR,NSList,ExpDR). 1013expand_dataRange(M,oneOf(DRs),NSList,oneOf(ExpDRs)) :- !, 1014 expand_dataRanges(M,DRs,NSList,ExpDRs). 1015expand_dataRange(M,datatypeRestriction(DR,FacetValues),NSList,datatypeRestriction(DRs,FacetValues)):- !, 1016 expand_datatype(M,DR,NSList,DRs), 1017 FacetValues=[_|_]. 1018expand_dataRange(M,literal(DR),NSList,ExpDR):- !, 1019 expand_literal(M,literal(DR),NSList,ExpDR). 1020expand_dataRange(M,DR,NSList,ExpDR) :- 1021 expand_datatype(M,DR,NSList,ExpDR), 1022 ( M:addKBName -> add_kb_atoms(M,datatype,[ExpDR]) ; true ).
Example: classExpression(intersectionOf([car,someValuesFrom(hasColor,blue)])))
Union of:
class/1 | objectIntersectionOf/1 | objectUnionOf/1 | objectComplementOf/1 | objectOneOf/1 | objectSomeValuesFrom/1 | objectAllValuesFrom/1 | objectHasValue/1 | objectHasSelf/1 | objectMinCardinality/1 | objectMaxCardinality/1 | objectExactCardinality/1 | dataSomeValuesFrom/1 | dataAllValuesFrom/1 | dataHasValue/1 | dataMinCardinality/1 | dataMaxCardinality/1 | dataExactCardinality/1
1040expand_classExpressions(_M,[],_NSList,[]) :- !. 1041expand_classExpressions(M,[CE|T],NSList,[ExpCE|ExpT]) :- 1042 expand_classExpression(M,CE,NSList,ExpCE), 1043 expand_classExpressions(M,T,NSList,ExpT). 1044 1045classExpression(CE):- 1046 (iri(CE) ; % NOTE: added to allow cases where class is not imported 1047 class(CE) ; 1048 objectIntersectionOf(CE) ; objectUnionOf(CE) ; objectComplementOf(CE) ; objectOneOf(CE) ; 1049 objectSomeValuesFrom(CE) ; objectAllValuesFrom(CE) ; objectHasValue(CE) ; objectHasSelf(CE) ; 1050 objectMinCardinality(CE) ; objectMaxCardinality(CE) ; objectExactCardinality(CE) ; 1051 dataSomeValuesFrom(CE) ; dataAllValuesFrom(CE) ; dataHasValue(CE) ; 1052 dataMinCardinality(CE) ; dataMaxCardinality(CE) ; dataExactCardinality(CE)),!. 1053/* 1054expand_classExpression(M,CE,NSList,ExpCE):- % TODO: add management datatype 1055 (expand_class(M,CE,NSList,ExpCE) ; % NOTE: added to allow cases where class is not imported 1056 expand_objectIntersectionOf(M,CE,NSList,ExpCE) ; expand_objectUnionOf(M,CE,NSList,ExpCE) ; expand_objectComplementOf(M,CE,NSList,ExpCE) ; expand_objectOneOf(M,CE,NSList,ExpCE) ; 1057 expand_objectSomeValuesFrom(M,CE,NSList,ExpCE) ; expand_objectAllValuesFrom(M,CE,NSList,ExpCE) ; expand_objectHasValue(M,CE,NSList,ExpCE) ; expand_objectHasSelf(M,CE,NSList,ExpCE) ; 1058 expand_objectMinCardinality(M,CE,NSList,ExpCE) ; expand_objectMaxCardinality(M,CE,NSList,ExpCE) ; expand_objectExactCardinality(M,CE,NSList,ExpCE) ; 1059 expand_dataSomeValuesFrom(M,CE,NSList,ExpCE) ; expand_dataAllValuesFrom(M,CE,NSList,ExpCE) ; expand_dataHasValue(M,CE,NSList,ExpCE) ; 1060 expand_dataMinCardinality(M,CE,NSList,ExpCE) ; expand_dataMaxCardinality(M,CE,NSList,ExpCE) ; expand_dataExactCardinality(M,CE,NSList,ExpCE)), 1061 ( M:addKBName -> add_kb_atoms(M,class,[ExpCE]) ; true ). 1062*/ 1063expand_classExpression(M,intersectionOf(CEs),NSList,intersectionOf(ExpCEs)):- !, 1064 expand_classExpressions(M,CEs,NSList,ExpCEs), 1065 ( M:addKBName -> add_kb_atoms(M,class,[intersectionOf(ExpCEs)]) ; true ). 1066expand_classExpression(M,unionOf(CEs),NSList,unionOf(ExpCEs)) :- !, 1067 expand_classExpressions(M,CEs,NSList,ExpCEs), 1068 ( M:addKBName -> add_kb_atoms(M,class,[unionOf(ExpCEs)]) ; true ). 1069 %add_rule(M,or_rule), 1070 %add_expressivity(M,a). 1071expand_classExpression(M,complementOf(CE),NSList,complementOf(ExpCE)) :- !, 1072 expand_classExpression(M,CE,NSList,ExpCE), 1073 ( M:addKBName -> add_kb_atoms(M,class,[complementOf(ExpCE)]) ; true ). 1074 %add_expressivity(M,a). 1075expand_classExpression(M,oneOf(Is),NSList,oneOf(ExpIs)) :- !, % TODO check in trill 1076 expand_individuals(M,Is,NSList,ExpIs), 1077 ( M:addKBName -> add_kb_atoms(M,class,[oneOf(ExpIs)]) ; true ). 1078 %add_rule(M,o_rule), 1079 %add_expressivity(M,o). 1080expand_classExpression(M,someValuesFrom(OPE,CE),NSList,someValuesFrom(ExpOPE,ExpCE)) :- !, 1081 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1082 expand_classExpression(M,CE,NSList,ExpCE), 1083 ( M:addKBName -> add_kb_atoms(M,class,[someValuesFrom(ExpOPE,ExpCE)]) ; true ). 1084 %add_rule(M,exists_rule). 1085expand_classExpression(M,allValuesFrom(OPE,CE),NSList,allValuesFrom(ExpOPE,ExpCE)) :- !, 1086 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1087 expand_classExpression(M,CE,NSList,ExpCE), 1088 ( M:addKBName -> add_kb_atoms(M,class,[allValuesFrom(ExpOPE,ExpCE)]) ; true ). 1089 %add_rule(M,forall_rule), 1090 %add_expressivity(M,a). 1091expand_classExpression(M,hasValue(OPE,I),NSList,hasValue(ExpOPE,ExpI)) :- !, % TODO: add in trill 1092 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1093 expand_individual(M,I,NSList,ExpI), 1094 ( M:addKBName -> add_kb_atoms(M,class,[hasValue(ExpOPE,ExpI)]) ; true ). 1095expand_classExpression(M,hasSelf(OPE),NSList,hasSelf(ExpOPE)) :- !, % TODO: add in trill 1096 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1097 ( M:addKBName -> add_kb_atoms(M,class,[hasSelf(ExpOPE)]) ; true ). 1098expand_classExpression(M,minCardinality(C,OPE,CE),NSList,minCardinality(C,ExpOPE,ExpCE)):- !, 1099 number(C), 1100 C>=0, 1101 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1102 expand_classExpression(M,CE,NSList,ExpCE), 1103 ( M:addKBName -> add_kb_atoms(M,class,[minCardinality(C,ExpOPE,ExpCE)]) ; true ). 1104 %add_rule(M,min_rule), 1105 %add_expressivity(M,q). 1106expand_classExpression(M,minCardinality(C,OPE),NSList,minCardinality(C,ExpOPE)):- !, 1107 number(C), 1108 C>=0, 1109 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1110 ( M:addKBName -> add_kb_atoms(M,class,[minCardinality(C,ExpOPE)]) ; true ). 1111 %add_rule(M,min_rule), 1112 %add_expressivity(M,n). 1113expand_classExpression(M,maxCardinality(C,OPE,CE),NSList,maxCardinality(C,ExpOPE,ExpCE)):- !, 1114 number(C), 1115 C>=0, 1116 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1117 expand_classExpression(M,CE,NSList,ExpCE), 1118 ( M:addKBName -> add_kb_atoms(M,class,[maxCardinality(C,ExpOPE,ExpCE)]) ; true ). 1119 %add_rule(M,max_rule), 1120 %add_expressivity(M,q). 1121expand_classExpression(M,maxCardinality(C,OPE),NSList,maxCardinality(C,ExpOPE)):- !, 1122 number(C), 1123 C>=0, 1124 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1125 ( M:addKBName -> add_kb_atoms(M,class,[maxCardinality(C,ExpOPE)]) ; true ). 1126 %add_rule(M,max_rule), 1127 %add_expressivity(M,n). 1128expand_classExpression(M,exactCardinality(C,OPE,CE),NSList,exactCardinality(C,ExpOPE,ExpCE)):- !, 1129 number(C), 1130 C>=0, 1131 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1132 expand_classExpression(M,CE,NSList,ExpCE), 1133 ( M:addKBName -> add_kb_atoms(M,class,[exactCardinality(C,ExpOPE,ExpCE)]) ; true ). 1134 %add_rule(M,min_rule),add_rule(M,max_rule), 1135 %add_expressivity(M,q). 1136expand_classExpression(M,exactCardinality(C,OPE),NSList,exactCardinality(C,ExpOPE)):- !, 1137 number(C), 1138 C>=0, 1139 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1140 ( M:addKBName -> add_kb_atoms(M,class,[exactCardinality(C,ExpOPE)]) ; true ). 1141 %add_rule(M,min_rule),add_rule(M,max_rule), 1142 %add_expressivity(M,n). 1143expand_classExpression(M,CE,NSList,ExpCE):- 1144 expand_class(M,CE,NSList,ExpCE), 1145 ( M:addKBName -> add_kb_atoms(M,class,[ExpCE]) ; true ).
intersectionOf(ClassExpression:list)
An intersection class expression IntersectionOf( CE1 ... CEn ) contains all individuals that are instances of all class expressions CEi for 1 <= i <= n.
1151objectIntersectionOf(intersectionOf(CEs)) :- 1152 forall(member(CE,CEs), 1153 classExpression(CE)). 1154expand_objectIntersectionOf(M,intersectionOf(CEs),NSList,intersectionOf(ExpCEs)) :- 1155 expand_classExpressions(M,CEs,NSList,ExpCEs).
1159objectUnionOf(unionOf(CEs)) :- 1160 forall(member(CE,CEs), 1161 classExpression(CE)). 1162expand_objectUnionOf(M,unionOf(CEs),NSList,unionOf(ExpCEs)) :- 1163 expand_classExpressions(M,CEs,NSList,ExpCEs).
1167objectComplementOf(complementOf(CE)) :- 1168 classExpression(CE). 1169expand_objectComplementOf(M,complementOf(CE),NSList,complementOf(ExpCE)) :- 1170 expand_classExpression(M,CE,NSList,ExpCE).
1174objectOneOf(oneOf(Is)) :- 1175 is_list(Is). % TODO: check if we need to strengthen this check 1176%objectOneOf(oneOf(Is)) :- 1177% forall(member(I,Is), 1178% individual(I)). 1179expand_objectOneOf(M,oneOf(Is),NSList,oneOf(ExpIs)) :- 1180 expand_individuals(M,Is,NSList,ExpIs).
1184objectSomeValuesFrom(someValuesFrom(OPE,CE)) :- 1185 objectPropertyExpression(OPE), 1186 classExpression(CE). 1187expand_objectSomeValuesFrom(M,someValuesFrom(OPE,CE),NSList,someValuesFrom(ExpOPE,ExpCE)) :- 1188 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1189 expand_classExpression(M,CE,NSList,ExpCE).
1193objectAllValuesFrom(allValuesFrom(OPE,CE)) :- 1194 objectPropertyExpression(OPE), 1195 classExpression(CE). 1196expand_objectAllValuesFrom(M,allValuesFrom(OPE,CE),NSList,allValuesFrom(ExpOPE,ExpCE)) :- 1197 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1198 expand_classExpression(M,CE,NSList,ExpCE).
1202objectHasValue(hasValue(OPE,I)) :- 1203 objectPropertyExpression(OPE), 1204 individual(I). 1205expand_objectHasValue(M,hasValue(OPE,I),NSList,hasValue(ExpOPE,ExpI)) :- 1206 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1207 expand_individual(M,I,NSList,ExpI).
1211objectHasSelf(hasSelf(OPE)) :- 1212 objectPropertyExpression(OPE). 1213expand_objectHasSelf(M,hasSelf(OPE),NSList,hasSelf(ExpOPE)) :- 1214 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE).
1218objectMinCardinality(minCardinality(C,OPE,CE)):- 1219 number(C), 1220 C>=0, 1221 objectPropertyExpression(OPE), 1222 classExpression(CE). 1223objectMinCardinality(minCardinality(C,OPE)):- 1224 number(C), 1225 C>=0, 1226 objectPropertyExpression(OPE). 1227expand_objectMinCardinality(M,minCardinality(C,OPE,CE),NSList,minCardinality(C,ExpOPE,ExpCE)):- 1228 number(C), 1229 C>=0, 1230 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1231 expand_classExpression(M,CE,NSList,ExpCE). 1232expand_objectMinCardinality(M,minCardinality(C,OPE),NSList,minCardinality(C,ExpOPE)):- 1233 number(C), 1234 C>=0, 1235 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE).
1239objectMaxCardinality(maxCardinality(C,OPE,CE)):- 1240 number(C), 1241 C>=0, 1242 objectPropertyExpression(OPE), 1243 classExpression(CE). 1244objectMaxCardinality(maxCardinality(C,OPE)):- 1245 number(C), 1246 C>=0, 1247 objectPropertyExpression(OPE). 1248expand_objectMaxCardinality(M,maxCardinality(C,OPE,CE),NSList,maxCardinality(C,ExpOPE,ExpCE)):- 1249 number(C), 1250 C>=0, 1251 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1252 expand_classExpression(M,CE,NSList,ExpCE). 1253expand_objectMaxCardinality(M,maxCardinality(C,OPE),NSList,maxCardinality(C,ExpOPE)):- 1254 number(C), 1255 C>=0, 1256 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE).
1260objectExactCardinality(exactCardinality(C,OPE,CE)):- 1261 number(C), 1262 C>=0, 1263 objectPropertyExpression(OPE), 1264 classExpression(CE). 1265objectExactCardinality(exactCardinality(C,OPE)):- 1266 number(C), 1267 C>=0, 1268 objectPropertyExpression(OPE). 1269% NON-NORMATIVE: we accept this in order to maximize compatibility with Thea1 1270objectExactCardinality(cardinality(C,OPE)):- 1271 number(C), 1272 C>=0, 1273 objectPropertyExpression(OPE). 1274expand_objectExactCardinality(M,exactCardinality(C,OPE,CE),NSList,exactCardinality(C,ExpOPE,ExpCE)):- 1275 number(C), 1276 C>=0, 1277 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE), 1278 expand_classExpression(M,CE,NSList,ExpCE). 1279expand_objectExactCardinality(M,exactCardinality(C,OPE),NSList,exactCardinality(C,ExpOPE)):- 1280 number(C), 1281 C>=0, 1282 expand_objectPropertyExpression(M,OPE,NSList,ExpOPE).
1286dataIntersectionOf(intersectionOf(DRs)) :- 1287 forall(member(DR,DRs), 1288 dataRange(DR)). 1289expand_dataIntersectionOf(M,intersectionOf(DRs),NSList,intersectionOf(ExpDRs)) :- 1290 expand_dataRanges(M,DRs,NSList,ExpDRs).
1294dataUnionOf(unionOf(DRs)) :- 1295 forall(member(DR,DRs), 1296 dataRange(DR)). 1297expand_dataUnionOf(M,unionOf(DRs),NSList,unionOf(ExpDRs)) :- 1298 expand_dataRanges(M,DRs,NSList,ExpDRs).
1302dataComplementOf(complementOf(DR)) :- 1303 dataRange(DR). 1304expand_dataComplementOf(M,complementOf(DR),NSList,complementOf(ExpDR)) :- 1305 expand_dataRange(M,DR,NSList,ExpDR).
1309dataOneOf(oneOf(DRs)) :- 1310 forall(member(DR,DRs), 1311 dataRange(DR)). 1312expand_dataOneOf(M,oneOf(DRs),NSList,oneOf(ExpDRs)) :- 1313 expand_dataRanges(M,DRs,NSList,ExpDRs).
TODO
: multiple args1318datatypeRestriction(datatypeRestriction(DR,FacetValues)):- 1319 datatype(DR), 1320 FacetValues=[_|_]. 1321expand_datatypeRestriction(M,datatypeRestriction(DR,FacetValues),NSList,datatypeRestriction(DRs,FacetValues)):- 1322 expand_datatype(M,DR,NSList,DRs), 1323 FacetValues=[_|_].
1326dataSomeValuesFrom(someValuesFrom(DPE,DR)):- 1327 dataPropertyExpression(DPE), 1328 dataRange(DR). 1329expand_dataSomeValuesFrom(M,someValuesFrom(DPE,DR),NSList,someValuesFrom(ExpDPE,ExpDR)):- 1330 expand_dataRange(M,DR,NSList,ExpDR), 1331 expand_dataPropertyExpression(M,DPE,NSList,ExpDPE).
1334dataAllValuesFrom(allValuesFrom(DPE,DR)):- 1335 dataPropertyExpression(DPE), 1336 dataRange(DR). 1337expand_dataAllValuesFrom(M,allValuesFrom(DPE,DR),NSList,allValuesFrom(ExpDPE,ExpDR)):- 1338 expand_dataRange(M,DR,NSList,ExpDR), 1339 expand_dataPropertyExpression(M,DPE,NSList,ExpDPE).
1343dataHasValue(hasValue(DPE,L)):- 1344 dataPropertyExpression(DPE), 1345 literal(L). 1346expand_dataHasValue(M,hasValue(DPE,L),NSList,hasValue(ExpDPE,ExpL)):- 1347 expand_literal(M,L,NSList,ExpL), 1348 expand_dataPropertyExpression(M,DPE,NSList,ExpDPE).
1352dataMinCardinality(minCardinality(C,DPE,DR)):- 1353 number(C), 1354 C>=0, 1355 dataPropertyExpression(DPE), 1356 dataRange(DR). 1357dataMinCardinality(minCardinality(C,DPE)):- 1358 number(C), 1359 C>=0, 1360 dataPropertyExpression(DPE). 1361expand_dataMinCardinality(M,minCardinality(C,DPE,DR),NSList,minCardinality(C,ExpDPE,ExpDR)):- 1362 number(C), 1363 C>=0, 1364 expand_dataRange(M,DR,NSList,ExpDR), 1365 expand_dataPropertyExpression(M,DPE,NSList,ExpDPE). 1366expand_dataMinCardinality(M,minCardinality(C,DPE),NSList,minCardinality(C,ExpDPE)):- 1367 number(C), 1368 C>=0, 1369 expand_dataPropertyExpression(M,DPE,NSList,ExpDPE).
1374dataMaxCardinality(maxCardinality(C,DPE,DR)):- 1375 number(C), 1376 C>=0, 1377 dataPropertyExpression(DPE), 1378 dataRange(DR). 1379dataMaxCardinality(maxCardinality(C,DPE)):- 1380 number(C), 1381 C>=0, 1382 dataPropertyExpression(DPE). 1383expand_dataMaxCardinality(M,maxCardinality(C,DPE,DR),NSList,maxCardinality(C,ExpDPE,ExpDR)):- 1384 number(C), 1385 C>=0, 1386 expand_dataRange(M,DR,NSList,ExpDR), 1387 expand_dataPropertyExpression(M,DPE,NSList,ExpDPE). 1388expand_dataMaxCardinality(M,maxCardinality(C,DPE),NSList,maxCardinality(C,ExpDPE)):- 1389 number(C), 1390 C>=0, 1391 expand_dataPropertyExpression(M,DPE,NSList,ExpDPE).
1396dataExactCardinality(exactCardinality(C,DPE,DR)):- 1397 number(C), 1398 C>=0, 1399 dataPropertyExpression(DPE), 1400 dataRange(DR). 1401dataExactCardinality(exactCardinality(C,DPE)):- 1402 number(C), 1403 C>=0, 1404 dataPropertyExpression(DPE). 1405% NON-NORMATIVE: we accept this in order to maximize compatibility with Thea1 1406dataExactCardinality(cardinality(C,OPE)):- 1407 number(C), 1408 C>=0, 1409 objectPropertyExpression(OPE). 1410expand_dataExactCardinality(M,exactCardinality(C,DPE,DR),NSList,exactCardinality(C,ExpDPE,ExpDR)):- 1411 number(C), 1412 C>=0, 1413 expand_dataRange(M,DR,NSList,ExpDR), 1414 expand_dataPropertyExpression(M,DPE,NSList,ExpDPE). 1415expand_dataExactCardinality(M,exactCardinality(C,DPE),NSList,exactCardinality(C,ExpDPE)):- 1416 number(C), 1417 C>=0, 1418 expand_dataPropertyExpression(M,DPE,NSList,ExpDPE).
1426is_valid_axiom(Axiom) :- \+ \+ valid_axiom(Axiom). 1427 1428 1429/**************************************** 1430 VIEW PREDICATES 1431 ****************************************/
1435equivalent_to(X,Y) :- equivalentClasses(L),member(X,L),member(Y,L),X\=Y. 1436equivalent_to(X,Y) :- equivalentProperties(L),member(X,L),member(Y,L),X\=Y. 1437 1438disjoint_with(X,Y) :- disjointClasses(L),member(X,L),member(Y,L),X\=Y.
1442anyPropertyAssertion(P,E,V) :- propertyAssertion(P,E,V). 1443anyPropertyAssertion(P,E,V) :- annotationAssertion(P,E,V).
1447labelAnnotation_value(X,Val) :- 1448 anyPropertyAssertion('http://www.w3.org/2000/01/rdf-schema#label', X, literal(type(_,Val))),atom(Val). 1449labelAnnotation_value(X,Val) :- 1450 anyPropertyAssertion('http://www.w3.org/2000/01/rdf-schema#label', X, literal(lang(_,Val))),atom(Val). 1451labelAnnotation_value(X,Val) :- 1452 anyPropertyAssertion('http://www.w3.org/2000/01/rdf-schema#label', X, literal(Val)),atom(Val). 1453 1454/**************************************** 1455 META-PREDICATES 1456 ****************************************/
e.g. axiom_directly_about( subClassOf(X,_), X)
.
also include property assertions whose second argument is equal to About.
e.g. axiom_directly_about( propertyAssertion(P,X,_), X)
.
1468axiom_directly_about(Ax,About) :- 1469 trill:axiom(Ax), 1470 Ax =.. [_,Arg1|_], 1471 ( is_list(Arg1) 1472 -> member(About,Arg1) 1473 ; About=Arg1). 1474axiom_directly_about(Ax,About) :- 1475 Ax=propertyAssertion(_,About,_), 1476 trill:axiom(Ax). 1477axiom_directly_about(Ax,About) :- 1478 Ax=annotationAssertion(_,About,_), 1479 trill:axiom(Ax). 1480axiom_directly_about(Ax,About) :- 1481 Ax=classAssertion(_,About), 1482 trill:axiom(Ax).
1491axiom_directly_references(Ax,Ref) :- 1492 trill:axiom(Ax), 1493 axiom_or_expression_references(Ax,Ref). 1494 1495axiom_or_expression_references(X,Ref) :- 1496 X =.. [P|Args], 1497 P\=literal, 1498 member(Arg,Args), 1499 ( is_list(Arg) 1500 -> member(Ref,Arg) 1501 ; Ref=Arg). 1502 1503axiom_about(Ax,About) :- 1504 axiom_directly_about(Ax,About). 1505axiom_about(Ax,About) :- 1506 axiom_directly_about(Ax,X), 1507 axiom_about(X,About). 1508 1509axiom_references(Ax,Ref) :- 1510 axiom_directly_references(Ax,Ref). 1511axiom_references(Ax,Ref) :- 1512 axiom_directly_references(Ax,X), 1513 axiom_or_expression_references(X,Ref). 1514 1515axiom_contains_expression(Ax,Ex) :- 1516 axiom_contains_expression(Ax,Ex,_). 1517axiom_contains_expression(Ax,Ex,D) :- 1518 trill:axiom(Ax), 1519 expression_has_subexpression(Ax,Ex,[],Chain), 1520 length(Chain,D). 1521 1522expression_has_subexpression(Ex,Ex,Accum,Accum). 1523expression_has_subexpression(Ex,SubEx,Accum,Results) :- 1524 Ex =.. [F|Args], 1525 member(A,Args), 1526 expression_has_subexpression(A,SubEx,[F|Accum],Results).
subClassOf(a,intersectionOf([b,someValuesFrom(p,c)]))
then Desc will be a member of [a, b, c, b and p some c, p some c]
1537referenced_description(C) :- 1538 setof(C,referenced_description_1(C),Cs), 1539 member(C,Cs). 1540 1541referenced_description_1(C) :- class(C). 1542referenced_description_1(C) :- 1543 subClassOf(A,B), 1544 ( referenced_description(A,C) 1545 ; referenced_description(B,C)). 1546referenced_description_1(C) :- 1547 equivalentClasses(L), 1548 member(A,L), 1549 referenced_description(A,C). 1550referenced_description_1(C) :- 1551 classAssertion(A,_), 1552 referenced_description(A,C). 1553 1554% TODO - this is incomplete 1555referenced_description(X,X) :- ground(X). 1556referenced_description(someValuesFrom(_,X),Y) :- referenced_description(X,Y). 1557referenced_description(allValuesFrom(_,X),Y) :- referenced_description(X,Y). 1558referenced_description(intersectionOf(L),Y) :- member(X,L),referenced_description(X,Y). 1559referenced_description(unionOf(L),Y) :- member(X,L),referenced_description(X,Y). 1560 1561 1562/**************************************** 1563 UTILITY 1564 ****************************************/ 1565 1566 1567%:- thread_local assert_axiom_hook/1.
this also asserts ontologyAxiom/2, using trdf_setting with current_ontology
1577assert_axiom(M,Axiom) :- 1578 ( M:ns4query(NSList) -> true; NSList = []), 1579 expand_axiom(M,Axiom,NSList,ExpAxiom), 1580 dif(ExpAxiom,'none'), 1581 ( M:ExpAxiom -> true 1582 ; 1583 ( assert(M:), 1584 ( M:trdf_setting(current_ontology,O) 1585 -> assert(M:ontologyAxiom(O,ExpAxiom)) 1586 ; true) 1587 ) 1588 ), !. 1589assert_axiom(_M,_Axiom).
1594assert_axiom(M,Axiom,_) :- 1595 M:Axiom, 1596 !. 1597assert_axiom(M,Axiom,O) :- 1598 assert(M:), 1599 assert(M:ontologyAxiom(O,Axiom)), 1600 !.
also removes ontologyAxiom/2 from ALL ontologies
1611retract_axiom(M,Axiom) :-
1612 retractall(M:),
1613 retractall(M:ontologyAxiom(_,Axiom)),
1614 !.
1618retract_axiom(M,Axiom,Ontology) :- 1619 \+ var(Ontology), 1620 retractall(M:ontologyAxiom(Ontology,Axiom)), 1621 ( \+ M:ontologyAxiom(_,Axiom) 1622 -> retractall(M:) 1623 ; true), % still exists in other ontology.. 1624 !. 1625 1626 1627retract_all_axioms(M) :- 1628 findall(M:A,trill:axiom(M:A),Axioms), 1629 maplist(retract,Axioms), 1630 findall(M:ontologyAxiom(O,A),M:ontologyAxiom(O,A),OAxioms), 1631 maplist(retract,OAxioms), 1632 !. 1633 1634 1635utility_translation_init(M) :- 1636 assert(M:annotationProperty('http://www.w3.org/2000/01/rdf-schema#label')), 1637 assert(M:annotationProperty('http://www.w3.org/2000/01/rdf-schema#comment')), 1638 assert(M:annotationProperty('https://sites.google.com/a/unife.it/ml/disponte#probability')), % Retro-compatibility 1639 assert(M:annotationProperty('http://ml.unife.it/disponte#probability')). 1640 1641consult_axioms(File) :- 1642 consult(File). 1643 1644axiom_type(A,T) :- functor(A,T,_). 1645 1646:- use_module(library(debug)). 1647:- use_module(library('semweb/rdf_db')). 1648:- use_module(library('semweb/rdf_edit')). 1649:- use_module(library('semweb/rdfs')). 1650:- use_module(library('url')). 1651:- use_module(library('http/http_open')). 1652:- use_module(library(charsio)). 1653 1654:- thread_local(owl/4). 1655:- thread_local(owl/3). 1656:- thread_local(owl/2). 1657:- dynamic owl/2.
1663:- thread_local(blanknode/3). 1664:- thread_local(outstream/1). 1665 1666:- thread_local(aNN/3). % implements the ANN(X) function. 1667:- thread_local(annotation_r_node/4). % annotation_r_node(S,P,O,Node) 1668:- thread_local(axiom_r_node/4). % axiom_r_node(S,P,O,Node) 1669:- thread_local(owl_repository/2). % implements a simple OWL repository: if URL not found, Ontology is read from a repository (local) RURL 1670 1671 1672% we make this discontiguous so that the code can follow the structure of the document as much as possible 1673 1674:- discontiguous owl_parse_axiom/4. 1675:- discontiguous dothislater/1. 1676 1677% hookable 1678 1679 1680% ----------------------------------------------------------------------- 1681% UTILITY Predicates 1682% -----------------------------------------------------------------------
1690owl_clear_as :- 1691 debug(owl_parser,'Clearing abstract syntax',[]), 1692 forall((axiompred(PredSpec),predspec_head(PredSpec,Head)), 1693 retractall(Head)). 1694 1695predspec_head(Pred/A,Head) :- functor(Head,Pred,A). 1696 1697u_assert(M,Term) :- 1698 call(M:Term), !; assert(M:). 1699 1700 1701convert(T,V,typed_value(T,V)).
1710rdf_2_owl(M,Ont) :- 1711 debug(owl_parser, 'Removing existing owl triples',[]), 1712% retractall(owl(_,_,_,Ont)), 1713 debug(owl_parser,'Copying RDF triples to OWL triples for Ontology ~w',[Ont]), 1714 M:rdf(X,Y,Z), 1715 assert(M:owl(X,Y,Z,Ont)), fail. 1716 1717rdf_2_owl(M,Ont) :- 1718 owl_count(M,Ont,Z), 1719 debug(owl_parser,'Number of owl triples copied: ~w',[Z]).
1725owl_count(M,O,U) :-
1726 findall(1,M:owl(_,_,_,O),X), length(X,U).
owl(S,P,O,not_used)
after expanding namespaces.
this is required for the triple replacement rules,
which use shortened rdfs/owl namespaces.
(or we could just use the expanded forms here which
may be faster..)
1735expand_and_assert(M,X1,Y1,Z1) :-
1736 expand_ns(X1,X),
1737 expand_ns(Y1,Y),
1738 expand_ns(Z1,Z),!,
1739 retractall(M:owl(X,Y,Z, used1)),
1740 assert(M:owl(X,Y,Z, not_used)).
owl(S,P,O)
in Triples has a non-ground variable then this will succeed
non-deterministically. If all variables are ground, then this
will succeed semi-deterministically.1749test_use_owl(_M,[]). 1750test_use_owl(M,[owl(S,P,O)|Rest]) :- 1751 test_use_owl(M,S,P,O), 1752 test_use_owl(M,Rest).
If any of S, P or O is non-ground then this will succeed non-deterministically. If all variables are ground, then this will succeed semi-deterministically.
1761test_use_owl(M,X1,Y1,Z1) :- 1762 expand_ns(X1,X), 1763 expand_ns(Y1,Y), 1764 expand_ns(Z1,Z),!, 1765 M:owl(X,Y,Z, not_used). 1766 1767test_use_owl(M,X1,Y1,Z1,named) :- 1768 expand_ns(X1,X), 1769 expand_ns(Y1,Y), 1770 expand_ns(Z1,Z), 1771 M:owl(X,Y,Z, not_used), 1772 \+ sub_string(X,0,1,_,'_').
1778use_owl(M,Triples) :- 1779 test_use_owl(M,Triples), 1780 use_owl_2(M,Triples). 1781 1782% consume all triples; we have already tested the list and know that all match 1783use_owl_2(_M,[]). 1784use_owl_2(M,[owl(S,P,O)|Triples]) :- 1785 use_owl(M,S,P,O), 1786 use_owl_2(M,Triples). 1787 1788 1789use_owl(M,X1,Y1,Z1) :- 1790 expand_ns(X1,X), 1791 expand_ns(Y1,Y), 1792 expand_ns(Z1,Z), 1793 M:owl(X,Y,Z, not_used), 1794 debug(owl_parser_detail,'using ~w ~w ~w',[X,Y,Z]), 1795 retract(M:owl(X,Y,Z, not_used)), 1796 assert(M:owl(X,Y,Z,used1)). 1797 1798use_owl(M,X1,Y1,Z1,named) :- 1799 expand_ns(X1,X), 1800 expand_ns(Y1,Y), 1801 expand_ns(Z1,Z), 1802 M:owl(X,Y,Z, not_used), 1803 \+ sub_string(X,0,1,_,'_'), 1804 retract(M:owl(X,Y,Z, not_used)), 1805 assert(M:owl(X,Y,Z,used2)). 1806 1807use_owl(M,X1,Y1,Z1,Term) :- 1808 expand_ns(X1,X), 1809 expand_ns(Y1,Y), 1810 expand_ns(Z1,Z), 1811 M:owl(X,Y,Z, not_used), 1812 debug(owl_parser_detail,'using ~w ~w ~w',[X,Y,Z]), 1813 retract(M:owl(X,Y,Z, not_used)), 1814 assert(M:owl(X,Y,Z,used(Term))).
1821use_owl(M,X1,Y1,Z1,named,Term) :-
1822 expand_ns(X1,X),
1823 expand_ns(Y1,Y),
1824 expand_ns(Z1,Z),
1825 M:owl(X,Y,Z, not_used),
1826 \+ sub_string(X,0,1,_,'_'),
1827 retract(M:owl(X,Y,Z, not_used)),
1828 assert(M:owl(X,Y,Z,used(Term))).
1835expand_ns(NS_URL, Full_URL) :- 1836 nonvar(NS_URL), 1837 NS_URL \= literal(_), 1838 uri_split(NS_URL,Short_NS,Term, ':'), 1839 rdf_db:ns(Short_NS,Long_NS),!, 1840 concat_atom([Long_NS,Term],Full_URL). 1841 1842expand_ns(URL, URL).
no_base(ShortNs)
: Use only term!1855collapse_ns(FullURL, NSURL,Char,Options) :- 1856 nonvar(FullURL), 1857 FullURL \= literal(_), 1858 uri_split(FullURL,LongNS, Term, '#'), 1859 concat(LongNS,'#',LongNS1), 1860 rdf_db:ns(ShortNS,LongNS1), 1861 ( member(no_base(ShortNS),Options), ! , NSURL = Term 1862 ; 1863 concat_atom([ShortNS,Char,Term],NSURL) 1864 ),!. 1865% CJM 1866collapse_ns(FullURL, NSURL,_Char,Options) :- 1867 nonvar(FullURL), 1868 \+ FullURL = literal(_), 1869 uri_split(FullURL,LongNS, Term, '#'), 1870 member(no_base(LongNS),Options), 1871 !, 1872 NSURL = Term. 1873 1874 1875collapse_ns(URL, URL,_,_).
concat(Namespace,Split_Char,Term)
1885uri_split(URI,Namespace,Term,Split_Char) :-
1886 sub_atom(URI,Start,_,After,Split_Char),
1887 sub_atom(URI,0,Start,_,Namespace),
1888 Start1 is Start + 1,
1889 sub_atom(URI,Start1,After,_,Term).
1894% Appends Node to the InList, and recursively, all other 1895% Nodes that are linked with the Predicate to the Node. The 1896% result is returned to OutList. 1897 1898owl_collect_linked_nodes(Node,Predicate,InList,OutList) :- 1899 get_module(M), 1900 use_owl(M,Node,Predicate,A),!, 1901 owl_collect_linked_nodes(Node,Predicate,InList,List1), 1902 owl_collect_linked_nodes(A,Predicate,List1,OutList). 1903 1904owl_collect_linked_nodes(Node,Predicate,InList,OutList) :- 1905 get_module(M), 1906 use_owl(M,A,Predicate,Node),!, 1907 owl_collect_linked_nodes(Node,Predicate,InList,List1), 1908 owl_collect_linked_nodes(A,Predicate,List1,OutList). 1909 1910owl_collect_linked_nodes(Node,_,List, [Node|List]) :- 1911 \+ memberchk(Node, List),!. 1912 1913owl_collect_linked_nodes(_,_,List, List) :- !. 1914 1915 1916% ---------------------------------------------------------------- 1917% OWL Parser implementation predicates 1918% ----------------------------------------------------------------
blanknode(Node,Description,used)
term.
The purpose is to record when a blank node has been used, so
subsequent uses of it will result in structure sharing.1928owl_get_bnode(M,Node,Description) :- 1929 sub_string(Node,0,1,_,'_'),!, 1930 \+ M:blanknode(Node,_,_), 1931 assert(M:blanknode(Node,Description, used)). 1932 1933owl_get_bnode(_,_,_). 1934 1935 1936 1937% ----------------------------------------------------------------------- 1938% Top Level Predicates 1939% ----------------------------------------------------------------------- 1940 1941/* 1942%% owl_parse(+URL, +RDF_Load_Mode, +OWL_Parse_Mode, +ImportFlag:boolean) 1943% 1944% Top level: parse a set of RDF triples and produce an 1945% AS representation of an OWL ontology. 1946% 1947% Calls the rdf_load_stream predicate to parse RDF stream in URL. 1948% If RDF_Load_Mode = complete it first retacts all rdf triples. 1949% If ImportFlag = true it handles owl:import clause at RDF level. 1950% 1951% This implements the mapping defined here: 1952% http://www.w3.org/TR/2008/WD-owl2-mapping-to-rdf-20081202/ 1953owl_parse(URL, RDF_Load_Mode, OWL_Parse_Mode,ImportFlag) :- 1954 ( RDF_Load_Mode=complete 1955 -> rdf_retractall(_,_,_), retractall(rdf_db:rdf_source(_,_,_,_)) 1956 ; true), 1957 ( OWL_Parse_Mode=complete 1958 -> owl_clear_as,retractall(blanknode(_,_,_)), retractall(owl(_,_,_,_)) 1959 ; true), 1960 !, 1961 debug(owl_parser,'Loading stream ~w',[URL]), 1962 owl_canonical_parse_2([URL],URL,ImportFlag,[],ProcessedIRIs), 1963 debug(owl_parser,'rdf_db populated, the following IRIs were processed: ~w',[ProcessedIRIs]), 1964 utility_translation_init, 1965 owl_canonical_parse_3(ProcessedIRIs). 1966 1967 1968%% owl_canonical_parse_2(+IRIs:list,+ParentIRI,+ImportFlag:boolean,+ProcessedURIsIn:list,?ProcessedURIsOut:list) is det 1969% recursively parses all ontologies in IRIs into rdf_db, ensuring none are processed twice. 1970owl_canonical_parse_2([],_,_,Processed,Processed) :- !. 1971 1972owl_canonical_parse_2([IRI|ToProcessRest],Parent,ImportFlag,ProcessedIn,ProcessedOut) :- 1973 member(IRI,ProcessedIn), 1974 !, 1975 owl_canonical_parse_2(ToProcessRest,Parent,ImportFlag,ProcessedIn,ProcessedOut). 1976 1977owl_canonical_parse_2([IRI|ToProcessRest],Parent,ImportFlag,ProcessedIn,ProcessedOut) :- 1978 % Get rdf triples, *Ontology* and Imports 1979 rdf_load_stream(IRI,O,BaseURI,Imports), 1980 ( nonvar(O) 1981 -> Ont = O 1982 ; Ont = Parent), % in the include case we may need to remove the import... 1983 debug(owl_parser,'Commencing rdf_2_owl. Generating owl/4',[]), 1984 rdf_2_owl(BaseURI,Ont), % move the RDF triples into the owl-Ont/4 facts 1985 ( ImportFlag = true 1986 -> owl_canonical_parse_2(Imports,Ont,ImportFlag,[Ont|ProcessedIn],ProcessedIn1) 1987 ; ProcessedIn1=[Ont|ProcessedIn]), 1988 owl_canonical_parse_2(ToProcessRest,Parent,ImportFlag,ProcessedIn1,ProcessedOut). 1989*/
1999owl_canonical_parse_3(_,[]). 2000 2001owl_canonical_parse_3(M,[IRI|Rest]) :- 2002 % Remove any existing not used owl fact 2003 retractall(M:owl(_,_,_,not_used)), 2004 % Copy the owl facts of the IRI document to the 'not_used' 2005 forall(M:owl(S,P,O,IRI),assert(M:owl(S,P,O,not_used))), 2006 2007 debug(owl_parser,'Anon individuals in reification [see table 8]',[]), 2008 2009 collect_r_nodes(M), 2010 2011 % Removed 2012 %forall(M:axiom_r_node(S,P,O,_Node),assert(M:owl(S,P,O,not_used))), 2013 2014 % First parse the Ontology axiom 2015 owl_parse_annotated_axioms(M,ontology/1), 2016 2017 debug(owl_parser,'Replacing patterns [see table 5]',[]),%QUA 2018 % remove triples based on pattern match (Table 5) 2019 ( forall((triple_remove(Pattern,Remove), test_use_owl(M,Pattern)), 2020 forall(member(owl(S,P,O),Remove),use_owl(M,S,P,O,removed))) -> true ; true), 2021 2022 2023 % temporary fix to make up for bug in rdf parsing 2024 % see email to JanW July-1-2009 2025 forall((test_use_owl(M,S,P,BNode), 2026 atom(BNode), 2027 sub_atom(BNode,0,1,_,'_'), 2028 test_use_owl(M,BNode,'http://www.w3.org/1999/02/22-rdf-syntax-ns#datatype',literal(_))), 2029 ( use_owl(M,S,P,BNode,datatype_fix), 2030 use_owl(M,BNode,'http://www.w3.org/1999/02/22-rdf-syntax-ns#datatype',literal(_)), 2031 expand_and_assert(M,S,P,literal('')))), 2032 2033 % replace matched patterns (Table 6) 2034 debug(owl_parser,'Replacing patterns [see table 6]',[]), 2035 ( setof(ReplaceWith, 2036 Pattern^( triple_replace(Pattern,ReplaceWith), % +Triples:list, ?Triples:list 2037 use_owl(M,Pattern), 2038 debug(owl_parser,'Replacing ~w ==> ~w [see table 6]',[Pattern,ReplaceWith])), 2039 ReplacementSetList) 2040 -> forall((member(ReplacementSet,ReplacementSetList),member(owl(S,P,O),ReplacementSet)), 2041 expand_and_assert(M,S,P,O)) 2042 ; debug(owl_parser,'No replacements required',[])), 2043 2044 /* 2045 forall(triple_replace(Pattern,ReplaceWith), 2046 forall(use_owl(M,Pattern), 2047 forall(member(owl(S,P,O),ReplaceWith), 2048 ( expand_and_assert(M,S,P,O), 2049 debug(owl_parser,'Replacing ~w ==> ~w [see table 6]',[Pattern,owl(S,P,O)]))))), 2050 */ 2051 2052 % continue with parsing using the rules... 2053 % Table 8, get the set of RIND - anonymous individuals in reification 2054 findall(X, (member(Y,['owl:Axiom','owl:Annotation', 2055 'owl:AllDisjointClasses','owl:AllDisjointProperties', 2056 'owl:AllDifferent','owl:NegativePropertyAssertion']), 2057 test_use_owl(M,X,'rdf:type',Y) 2058 ), 2059 RIND), 2060 set_trdf(rind,RIND), 2061 2062 % Table 9, row 5 2063 % VV 10/3/2010 get the annotation properties before collecting the annotations. 2064 debug(owl_parser,'asserting annotationProperty/1 for all APs',[]), 2065 forall( test_use_owl(M,D,'rdf:type','owl:AnnotationProperty'), 2066 assert_axiom(M,annotationProperty(D))), 2067 2068 % TODO - make this faster 2069 debug(owl_parser,'Implements function ANN(x) 3.2.2 Table 10.',[]), 2070 findall(_,ann(M,_,_),_), % find all annotations, assert annotation(X,AP,AV) axioms. 2071 2072 debug(owl_parser,'Commencing parse of annotated axioms',[]), 2073 forall((axiompred(PredSpec),\+dothislater(PredSpec),\+omitthis(PredSpec)), 2074 owl_parse_annotated_axioms(M,PredSpec)), 2075 forall((axiompred(PredSpec),dothislater(PredSpec),\+omitthis(PredSpec)), 2076 owl_parse_annotated_axioms(M,PredSpec)), 2077 2078 % annotated complex axioms, s.a., equivalentClasses([a,intersectionOf(..)]) that are 2079 % seen in axiom_r_node as axiom_r_node(a,intersectionOf,_:DescriptionX,_:DescriptionY) 2080 2081 2082 2083 debug(owl_parser_detail,'Commencing parse of unannotated axioms',[]), 2084 forall((axiompred(PredSpec),\+dothislater(PredSpec),\+omitthis(PredSpec)), 2085 owl_parse_nonannotated_axioms(M,PredSpec)), 2086 forall((axiompred(PredSpec),dothislater(PredSpec),\+omitthis(PredSpec)), 2087 owl_parse_nonannotated_axioms(M,PredSpec)),!, 2088 2089 % annotation Assertion 2090 parse_annotation_assertions(M), 2091 forall(owl_parse_compatibility_DL(M,Axiom),assert_axiom(M,Axiom)), 2092 owl_canonical_parse_3(M,Rest). 2093 2094omitthis(ontology/1). 2095 2096 2097owl_parse_annotated_axioms(M,Pred/Arity) :- 2098 debug(owl_parser_detail,'[ann] Parsing all of type: ~w',[Pred]), 2099 functor(Head,Pred,Arity), 2100% forall(owl_parse_axiom(M,Mod:Head), 2101% ( debug(owl_parser_detail,' parsed: [~w] ~w',[Mod,Head]), 2102% assert(Mod:Head))). 2103 forall(owl_parse_axiom(M,Head,true,Annotations), 2104 ( assert_axiom(M,Head), 2105 debug(owl_parser_detail_anns,' parsed: ~w : anns: ~w',[Head,Annotations]), 2106 forall(member(X,Annotations), 2107 forall(M:aNN(X,AP,AV), 2108 assert_axiom(M,annotation(Head,AP,AV)) 2109 ) 2110 ) 2111 ) 2112 ), 2113 debug(owl_parser_detail,'[ann] Done parsing all of type: ~w',[Pred]). 2114 2115owl_parse_nonannotated_axioms(M,Pred/Arity) :- 2116 debug(owl_parser_detail,'[unann] Parsing all of type: ~w',[Pred]), 2117 functor(Head,Pred,Arity), 2118 forall(owl_parse_axiom(M,Head,false,_), 2119 assert_axiom(M,Head) 2120 ).
If owl_repository/2 is defined, then this is used to map URLs prior to loading.
2136rdf_load_stream(URL,Ontology,BaseURI,Imports) :- 2137 owl_repository(URL,RURL), 2138 !, 2139 % note: users responsibility to avoid infinite loops by avoid cycles in repository mappings! 2140 rdf_load_stream(RURL,Ontology,BaseURI,Imports). 2141 2142rdf_load_stream(URL,Ontology,BaseURI,Imports) :- 2143 BaseURI = URL, 2144 ( sub_atom(URL,0,4,_,'http') 2145 -> catch((http_open(URL,RDF_Stream,[]), 2146 rdf_load(RDF_Stream,[if(true),base_uri(BaseURI),blank_nodes(noshare), 2147 result(Action, Triples, MD5),register_namespaces(true)]), 2148 debug(owl_parser,' Loaded ~w stream: ~w Action: ~w Triples:~w MD5: ~w',[URL,RDF_Stream,Action,Triples,MD5]), 2149 close(RDF_Stream)), 2150 Message, 2151 throw(io_error(URL,'rdf_load/2 failed',Message))) % re-throw with more information 2152 ; RDF_Stream = URL, rdf_load(RDF_Stream,[blank_nodes(noshare),if(true),base_uri(BaseURI),register_namespaces(true)]) 2153 ), 2154 % collect all imports directives 2155 ( rdf(Ontology,'http://www.w3.org/1999/02/22-rdf-syntax-ns#type','http://www.w3.org/2002/07/owl#Ontology',BaseURI:_) 2156 -> findall(I,rdf(Ontology,'http://www.w3.org/2002/07/owl#imports',I,BaseURI:_),Imports) 2157 ; Imports = [] 2158 ). 2159 2160 2161 2162% ---------------------------------------------------------------- 2163% 3 Mapping from RDF Graphs to the Structural Specification 2164% ---------------------------------------------------------------- 2165 2166/* 2167 2168 This section specifies the results of steps CP-2.2 and CP-3.3 of the 2169 canonical parsing process from Section 3.6 of the OWL 2 2170 Specification [OWL 2 Specification] on an ontology document D that 2171 can be parsed into an RDF graph G. ... 2172 2173 */ 2174 2175% owl_description_list(+Module,+Node, -List) 2176% 2177% If +Node is defined as rdf:type rdf:List, then List returns 2178% a prolog list of descriptions for this Node. 2179 2180owl_description_list(_M,'http://www.w3.org/1999/02/22-rdf-syntax-ns#nil',[]) :- !. 2181 2182owl_description_list(M,X,[F|R]) :- 2183 % use_owl(M,X,'rdf:type','rdf:List',list), % this is now removed from graph 2184 use_owl(M,X,'rdf:first',Element,first), 2185 owl_description(M,Element,F), 2186 use_owl(M,X,'rdf:rest',Y,rest), 2187 !,owl_description_list(M,Y,R). 2188 2189 2190% owl_individual_list(+Module,+Node, -List) 2191% 2192% If +Node is defined as rdf:type rdf:List, then List returns 2193% a prolog list of individuals for this Node. 2194 2195owl_individual_list(_M,'http://www.w3.org/1999/02/22-rdf-syntax-ns#nil',[]) :- !. 2196 2197owl_individual_list(M,X,[F|R]) :- 2198 % use_owl(M,X,'rdf:type','rdf:List',list), % this is now removed from graph 2199 use_owl(M,X,'rdf:first',F,first), 2200 use_owl(M,X,'rdf:rest',Y,rest), 2201 !,owl_individual_list(M,Y,R). 2202 2203% owl_property_list(+Module,+Node, -List) 2204% 2205% If +Node is defined as rdf:type rdf:List, then List returns 2206% a prolog list of properties for this Node. 2207 2208owl_property_list(_M,'http://www.w3.org/1999/02/22-rdf-syntax-ns#nil',[]) :- !. 2209 2210owl_property_list(M,X,[F|R]) :- 2211 % use_owl(M,X,'rdf:type','rdf:List',list), % this is now removed from graph 2212 use_owl(M,X,'rdf:first',Element,first), 2213 owl_property_expression(M,Element,F), 2214 use_owl(M,X,'rdf:rest',Y,rest), 2215 !,owl_property_list(M,Y,R). 2216 2217% owl_datarange_list(+Module,+Node, -List) 2218% 2219% If +Node is defined as rdf:type rdf:List, then List returns 2220% a prolog list of dataranges for this Node. 2221 2222owl_datarange_list(_,'http://www.w3.org/1999/02/22-rdf-syntax-ns#nil',[]) :- !. 2223 2224owl_datarange_list(M,X,[F|R]) :- 2225 % use_owl(M,X,'rdf:type','rdf:List',list), % this is now removed from graph 2226 use_owl(M,X,'rdf:first',Element,first), 2227 owl_datarange(M,Element,F), 2228 use_owl(M,X,'rdf:rest',Y,rest), 2229 !,owl_datarange_list(M,Y,R). 2230 2231% owl_datatype_restriction_list(+Node, -List) 2232% 2233% If +Node is defined as rdf:type rdf:List, then List returns 2234% a prolog list of datatype restrictions for this Node. 2235 2236owl_datatype_restriction_list('http://www.w3.org/1999/02/22-rdf-syntax-ns#nil',[]) :- !. 2237 2238owl_datatype_restriction_list(X,[facetRestriction(W2,L)|R]) :- 2239 % use_owl(M,X,'rdf:type','rdf:List'), % this is now removed from graph 2240 use_owl(M,X,'rdf:first',Element,first_datatype_restr), 2241 use_owl(M,Element,W,L,datatype_restr), 2242 ( concat_atom([_,W2],'#',W) 2243 -> true 2244 ; W2=W), 2245 use_owl(M,X,'rdf:rest',Y,rest_datatype_restr), 2246 !,owl_datatype_restriction_list(Y,R). 2247 2248 2249% 3.1 Extracting Declarations and the IRIs of the Directly Imported Ontology Documents 2250% This section specifies the result of step CP-2.2 of the canonical parsing process on an RDF graph G 2251 2252 2253% 3.1.2 Parsing of the Ontology Header and Declarations 2254 2255% Table 4. 2256owl_parse_axiom(M,ontology(O),AnnMode,List) :- 2257 test_use_owl(M,O,'rdf:type','owl:Ontology'), 2258 \+ test_use_owl(M,[owl(U,_W,O),owl(U,'rdf:type','owl:Ontology')]), 2259 valid_axiom_annotation_mode(AnnMode,M,O,'rdf:type','owl:Ontology',List), 2260 use_owl(M,O,'rdf:type','owl:Ontology',ontology), 2261 set_trdf(current_ontology,O), 2262 forall(use_owl(M,O,'owl:imports',IRI,ontology_import), assert_axiom(M,ontologyImport(O,IRI))), 2263 forall(use_owl(M,O,'owl:versionInfo',IRI2,ontology_version_info), assert_axiom(M,ontologyVersionInfo(O,IRI2))),!. % Do Once 2264 2265 2266% See table 5. 2267% triple_remove(Pattern:list,Remove:list) 2268% if Pattern is present, remove triples in Remove 2269triple_remove([owl(X,'rdf:type','owl:Ontology')],[owl(X,'rdf:type','owl:Ontology')]). 2270triple_remove([owl(X,'rdf:type','owl:Class'),owl(X,'rdf:type','rdfs:Class')],[owl(X,'rdf:type','rdfs:Class')]). 2271triple_remove([owl(X,'rdf:type','rdfs:Datatype'),owl(X,'rdf:type','rdfs:Class')],[owl(X,'rdf:type','rdfs:Class')]). 2272triple_remove([owl(X,'rdf:type','owl:DataRange'),owl(X,'rdf:type','rdfs:Class')],[owl(X,'rdf:type','rdfs:Class')]). 2273triple_remove([owl(X,'rdf:type','owl:Restriction'),owl(X,'rdf:type','rdfs:Class')],[owl(X,'rdf:type','rdfs:Class')]). 2274triple_remove([owl(X,'rdf:type','owl:Restriction'),owl(X,'rdf:type','owl:Class')],[owl(X,'rdf:type','owl:Class')]). 2275triple_remove([owl(X,'rdf:type','owl:ObjectProperty'),owl(X,'rdf:type','rdf:Property')],[owl(X,'rdf:type','rdf:Property')]). 2276triple_remove([owl(X,'rdf:type','owl:FunctionalProperty'),owl(X,'rdf:type','rdf:Property')],[owl(X,'rdf:type','rdf:Property')]). 2277triple_remove([owl(X,'rdf:type','owl:InverseFunctionalProperty'),owl(X,'rdf:type','rdf:Property')],[owl(X,'rdf:type','rdf:Property')]). 2278triple_remove([owl(X,'rdf:type','owl:TransitiveProperty'),owl(X,'rdf:type','rdf:Property')],[owl(X,'rdf:type','rdf:Property')]). 2279triple_remove([owl(X,'rdf:type','owl:DatatypeProperty'),owl(X,'rdf:type','rdf:Property')],[owl(X,'rdf:type','rdf:Property')]). 2280triple_remove([owl(X,'rdf:type','owl:AnnotationProperty'),owl(X,'rdf:type','rdf:Property')],[owl(X,'rdf:type','rdf:Property')]). 2281triple_remove([owl(X,'rdf:type','owl:OntologyProperty'),owl(X,'rdf:type','rdf:Property')],[owl(X,'rdf:type','rdf:Property')]). 2282triple_remove([owl(X,'rdf:type','rdf:List'),owl(X,'rdf:first',_Y),owl(X,'rdf:rest',_Z)],[owl(X,'rdf:type','rdf:List')]). 2283/* 2284 triple_remove([owl(X,'rdf:type','owl:Thing')],[owl(X,'rdf:type','owl:Thing')]). 2285*/ 2286% See table 6. 2287% http://www.w3.org/TR/2008/WD-owl2-mapping-to-rdf-20081202/ 2288triple_replace([owl(X,'rdf:type','owl:OntologyProperty')],[owl(X,'rdf:type','owl:AnnotationProperty')]). 2289triple_replace([owl(X,'rdf:type','owl:InverseFunctionalProperty')],[owl(X,'rdf:type','owl:ObjectProperty'),owl(X,'rdf:type','owl:InverseFunctionalProperty')]). 2290triple_replace([owl(X,'rdf:type','owl:TransitiveProperty')],[owl(X,'rdf:type','owl:ObjectProperty'),owl(X,'rdf:type','owl:TransitiveProperty')]). 2291triple_replace([owl(X,'rdf:type','owl:SymmetricProperty')],[owl(X,'rdf:type','owl:ObjectProperty'),owl(X,'rdf:type','owl:SymmetricProperty')]). 2292 2293% NOTE: this is not specified in table 6. However, we treat rdfs:Classes as equivalent to owl:Classes 2294triple_replace([owl(X,'rdf:type','rdfs:Class')],[owl(X,'rdf:type','owl:Class')]). 2295 2296% DECLARATIONS 2297% 2298% See table 7. 2299% http://www.w3.org/TR/2008/WD-owl2-mapping-to-rdf-20081202/
2305owl_parse_axiom(M,class(C),AnnMode,List) :- 2306 test_use_owl(M,C,'rdf:type','owl:Class'), 2307 valid_axiom_annotation_mode(AnnMode,M,C,'rdf:type','owl:Class',List), 2308 ( use_owl(M,C,'rdf:type','owl:Class',named,class(C)) -> true ; use_owl(M,C,'rdf:type','rdfs:Class',named,class(C))), 2309 \+ M:class(C). 2310 2311 2312owl_parse_axiom(M,datatype(D), AnnMode, List) :- 2313 test_use_owl(M,D,'rdf:type','rdf:Datatype'), 2314 valid_axiom_annotation_mode(AnnMode,M,D,'rdf:type','rdf:Datatype',List), 2315 use_owl(M,D,'rdf:type','rdf:Datatype',datatype(D)). 2316 2317 2318owl_parse_axiom(M,objectProperty(D), AnnMode, List) :- 2319 test_use_owl(M,D,'rdf:type','owl:ObjectProperty'), 2320 valid_axiom_annotation_mode(AnnMode,M,D,'rdf:type','owl:ObjectProperty',List), 2321 use_owl(M,D,'rdf:type','owl:ObjectProperty',objectProperty(D)), 2322 \+ M:objectProperty(D). 2323 2324 2325% note the difference in names between syntax and rdf 2326owl_parse_axiom(M,dataProperty(D), AnnMode, List) :- 2327 test_use_owl(M,D,'rdf:type','owl:DatatypeProperty'), 2328 valid_axiom_annotation_mode(AnnMode,M,D,'rdf:type','rdf:DatatypeProperty',List), 2329 use_owl(M,D,'rdf:type','owl:DatatypeProperty',dataProperty(D)), 2330 \+ M:dataProperty(D). 2331 2332owl_parse_axiom(M,annotationProperty(D), AnnMode, List) :- 2333 test_use_owl(M,D,'rdf:type','owl:AnnotationProperty'), 2334 valid_axiom_annotation_mode(AnnMode,M,D,'rdf:type','rdf:AnnotationProperty',List), 2335 use_owl(M,D,'rdf:type','owl:AnnotationProperty',annotationProperty(D)), 2336 \+ M:annotationProperty(D). 2337 2338 2339% TODO: check this. do we need to assert individual axioms if all we have is an rdf:type? 2340owl_parse_axiom(M,namedIndividual(D), AnnMode, List) :- 2341 test_use_owl(M,D,'rdf:type','owl:NamedIndividual'), 2342 valid_axiom_annotation_mode(AnnMode,M,D,'rdf:type','rdf:NamedIndividual',List), 2343 use_owl(M,D,'rdf:type','owl:NamedIndividual',namedIndividual(D)). 2344 2345 2346% Table 8. Identifying Anonymous Individuals in Reification 2347% TODO 2348 2349 2350% 3.2 Populating an Ontology 2351 2352 2353% 3.2.1 Analyzing Declarations 2354 2355% 3.2.2 Parsing of Annotations 2356 2357% 2358% ann(+Module,?X, -Extension List) 2359% 2360% Implements function ANN(x) 3.2.2 Table 10 2361% 2362% The annotations in G are parsed next. The function ANN assigns a 2363% set of annotations ANN(x) to each IRI or blank node x. This 2364% function is initialized by setting ANN(x) = a.. for each each IRI 2365% or blank node x. Next, the triple patterns from Table 10 are 2366% matched in G and, for each matched pattern, ANN(x) is extended 2367% with an annotation from the right column. Each time one of these 2368% triple patterns is matched, the matched triples are removed from 2369% G. This process is repeated until no further matches are 2370% possible 2371 2372ann(M,X,Y) :- 2373 ann(M,X,X,Y). 2374 2375 2376 2377ann(M,X,X1, annotation(X1,Y,Z)) :- 2378 M:annotationProperty(Y), 2379 debug(owl_parser_detail,'annotation property: ~w',[Y]), 2380 M:owl(X,Y,Z,not_used), 2381 use_owl(M,X,Y,Z,annotationProperty(Y)), 2382 u_assert(M,aNN(X1,Y,Z)), 2383 ann2(M,X,Y,Z,X1). 2384 2385 2386ann2(M,X,Y,Z,X1) :- 2387 M:annotation_r_node(X,Y,Z,W), 2388 ann(M,W,annotation(X1,Y,Z),Term), 2389 u_assert(M,Term). 2390 2391ann2(M,X,Y,Z,X1) :- 2392 M:axiom_r_node(X,Y,Z,W), 2393 ann(M,W,annotation(X1,Y,Z),Term), 2394 u_assert(M,Term). 2395 2396 2397ann2(_,_,_,_,_). 2398 2399 2400% 3.2.4 Parsing of Expressions 2401 2402is_bnode(C) :- 2403 atom(C), 2404 sub_atom(C,0,1,_,'_'). 2405 2406 2407 % Table 11. Parsing Object Property Expressions 2408owl_property_expression(_M,C,C) :- 2409 \+ is_bnode(C), % better: IRI(C). 2410 % VV added 10/3/2011 2411 C\='http://www.w3.org/1999/02/22-rdf-syntax-ns#first', 2412 C\='http://www.w3.org/1999/02/22-rdf-syntax-ns#rest', 2413 !. 2414 2415owl_property_expression(M,C,D) :- 2416 M:blanknode(C,D,Use), 2417 ( Use = used, 2418 retractall(M:blanknode(C,D,used)), 2419 assert(M:blanknode(C,D,shared)) 2420 ; 2421 true). 2422 2423owl_property_expression(M,P,inverseOf(Q)) :- 2424 use_owl(M,P,'owl:inverseOf',Q,inverseof(P,Q)), 2425 owl_get_bnode(M,P,inverseOf(Q)). 2426 2427 2428% Table 12. Parsing of Data Ranges 2429 2430owl_datarange(_M,D,D) :- 2431 \+ is_bnode(D),!. % better: IRI(C). 2432 2433owl_datarange(M,C,D) :- 2434 M:blanknode(C,D,Use), 2435 ( Use = used, 2436 retractall(M:blanknode(C,D,used)), 2437 assert(M:blanknode(C,D,shared)) 2438 ; 2439 true). 2440 2441owl_datarange(M,D,intersectionOf(L)) :- 2442 use_owl(M,D,'rdf:type','rdfs:Datatype',datarange(D)), 2443 use_owl(M,D,'owl:intersectionOf',Y,datarange(D)), 2444 %print(D-inter-Y),nl, 2445 owl_datarange_list(M,Y,L), 2446 owl_get_bnode(M,D,intersectionOf(L)). 2447 2448owl_datarange(M,D,unionOf(L)) :- 2449 use_owl(M,D,'rdf:type','rdfs:Datatype',datarange(D)), 2450 use_owl(M,D,'owl:unionOf',Y,datarange(D)), 2451 owl_datarange_list(M,Y,L), 2452 owl_get_bnode(M,D,unionOf(L)). 2453 2454 2455owl_datarange(M,D,complementOf(DY)) :- 2456 use_owl(M,D,'rdf:type','rdfs:Datatype',dataRange(D)), 2457 use_owl(M,D,'owl:datatypeComplementOf',Y,datacomplement(D)), 2458 owl_datarange(M,Y,DY), 2459 owl_get_bnode(M,D,complementOf(DY)). 2460 2461% Table 14, case 2 2462 owl_datarange(M,D,complementOf('rdfs:Literal')) :- 2463 use_owl(M,D,'rdf:type','rdfs:DataRange',dataRange(D)), 2464 use_owl(M,D,'owl:oneOf',[],oneOf(D)), 2465 owl_get_bnode(M,D,complementOf('rdfs:Literal')). 2466 2467owl_datarange(M,D,oneOf(L)) :- 2468 use_owl(M,D,'rdf:type','rdfs:Datatype',dataType(D)), 2469 use_owl(M,D,'owl:oneOf',L1,oneOf(D)), 2470 owl_individual_list(M,L1,L), 2471 owl_get_bnode(M,D,oneOf(L)). 2472 2473% Table 14, case 1 2474owl_datarange(M,D,oneOf(L)) :- 2475 use_owl(M,D,'rdf:type','rdfs:DataRange',datarange(D)), 2476 use_owl(M,D,'owl:oneOf',L1,datarange(D)), 2477 owl_individual_list(M,L1,L), 2478 owl_get_bnode(M,D,oneOf(L)). 2479 2480 2481owl_datarange(M,D,datatypeRestriction(DY,L)) :- 2482 use_owl(M,D,'rdf:type','rdfs:Datatype',datarange(D)), 2483 use_owl(M,D,'owl:onDatatype',Y,datarange(D)), 2484 owl_datarange(M,Y,DY), 2485 use_owl(M,D,'owl:withRestrictions',L1,datarange(D)), 2486 owl_datatype_restriction_list(L1,L), 2487 owl_get_bnode(M,D,datatypeRestriction(DY,L)). 2488 2489% Table 13. Parsing of Class Expressions 2490 2491% ---------------------------------------------------------------------- 2492% owl_description(+Module,+Node,-Description). 2493% 2494% It implements OWL AS production rules for Descriptions. 2495% During the construction of the Description any blank node 2496% is recorded for later structure sharing checks. 2497 2498owl_description(_M,C,C) :- 2499 \+ is_bnode(C),!. % better: IRI(C). 2500 2501 2502owl_description(M,C,D) :- 2503 M:blanknode(C,D,Use), 2504 ( Use = used, 2505 retractall(M:blanknode(C,D,used)), 2506 assert(M:blanknode(C,D,shared)) 2507 ; 2508 true),!. 2509 2510% TODO: this leaves behind classAssertions of type owlClass for the bnodes 2511owl_description(M,D,intersectionOf(L)) :- 2512 use_owl(M,D,'owl:intersectionOf',L1,intersectionOf(D)), 2513 owl_description_list(M,L1,L), 2514 \+L = [], 2515 owl_get_bnode(M,D,intersectionOf(L)),!. 2516 2517owl_description(M,D,unionOf(L)) :- 2518 use_owl(M,D,'owl:unionOf',L1,union(D)), 2519 owl_description_list(M,L1,L), 2520 owl_get_bnode(M,D,unionOf(L)),!. 2521 2522 2523owl_description(M,D,complementOf(Descr)) :- 2524 use_owl(M,D,'owl:complementOf',D1,complementOf(D)), 2525 owl_description(M,D1,Descr), 2526 owl_get_bnode(M,D,complementOf(Descr)),!. 2527 2528owl_description(M,D,oneOf(L)) :- 2529 use_owl(M,D,'owl:oneOf',L1,oneOf(D)), 2530 ( use_owl(M,D,'rdf:type','owl:Class',oneOf(D,L)) ; true), 2531 owl_individual_list(M,L1,L), 2532 owl_get_bnode(M,D,oneOf(L)),!. 2533 2534owl_description(M,D,datatypeRestriction(DY,L)) :- 2535 use_owl(M,D,'rdf:type','rdfs:Datatype',datatypeRestr(D)), 2536 use_owl(M,D,'owl:onDatatype',Y,dataType(D)), 2537 owl_datarange(M,Y,DY), 2538 use_owl(M,D,'owl:withRestrictions',L1,withRestrictions(D)), 2539 owl_datatype_restriction_list(L1,L), 2540 owl_get_bnode(M,D,datatypeRestriction(DY,L)). 2541 2542owl_description(M,D,Restriction) :- 2543 owl_restriction(M,D, Restriction), 2544 owl_get_bnode(M,D,Restriction),!. 2545 2546 2547% Table 15 - OWL DL compatibility class expressions 2548% 2549owl_description(M,D,Result) :- 2550 \+ is_bnode(D), % better: IRI(C). 2551 use_owl(M,D,'rdf:type','owl:Class',description(D)), 2552 use_owl(M,D,'owl:unionOf',L,unionOf(L)), 2553 owl_description_list(M,L,DL), 2554 ( DL = [], Result = 'owl:Nothing' ; 2555 DL = [D1], Result = D1), 2556 owl_get_bnode(M,D,Result),!. 2557 2558owl_description(M,D,Result) :- 2559 \+ is_bnode(D), % better: IRI(C). 2560 use_owl(M,D,'rdf:type','owl:Class',dl_compatibility_descr(D)), 2561 use_owl(M,D,'owl:intersectionOf',L,intersectionOf(D)), 2562 owl_description_list(M,L,DL), 2563 ( DL = [], Result = 'owl:Thing' ; 2564 DL = [D1], Result = D1), 2565 owl_get_bnode(M,D,Result),!. 2566 2567owl_description(M,D,Result) :- 2568 \+ is_bnode(D),!, % better: IRI(C). 2569 use_owl(M,D,'rdf:type','owl:Class',dl_compatibility_descr(D)), 2570 use_owl(M,D,'owl:oneOf',[],oneOf(D)), 2571 Result = 'owl:Nothing', 2572 owl_get_bnode(M,D,Result). 2573 2574% support older deprecated versions of OWL2 spec. See for example hydrology.owl 2575onClass(M,E,D) :- use_owl(M,E,'http://www.w3.org/2006/12/owl2#onClass',D,onClass(E)). 2576onClass(M,E,D) :- use_owl(M,E,'owl:onClass',D,onClass(E)). 2577 2578onDataRange(M,E,D) :- use_owl(M,E, 'owl:onDataRange',D,onDatarange(E)). 2579 2580 2581% owl_restriction(+Module,+Element,-Restriction). 2582% 2583% If Element is defined as a owl:Restriction on property P then 2584% Restriction binds to a restriction(Property,Type) term, 2585% according to OWL Abstract syntax specification. 2586 2587owl_restriction(M,Element,Restriction) :- 2588 use_owl(M,Element,'rdf:type','owl:Restriction',restriction(Element)), 2589 ( use_owl(M,Element, 'owl:onProperty',PropertyID,onProperty(Element,PropertyID)) ; 2590 use_owl(M,Element, 'owl:onProperties',PropertyID,onProperties(Element,PropertyID)) 2591 ), 2592 owl_restriction_type(M,Element,PropertyID, Restriction), 2593 debug(owl_parser_detail,'Restriction: ~w',[Restriction]). 2594 2595 2596 2597owl_restriction_type(M,E, P, someValuesFrom(PX, DX)) :- 2598 use_owl(M,E, 'owl:someValuesFrom',D,someValuesFrom(E,P)), 2599 ( owl_description(M,D, DX) ; owl_datarange(M,D,DX)), 2600 ( P = [_|_], owl_property_list(M,P,PX) ; owl_property_expression(M,P, PX)). 2601 2602 2603owl_restriction_type(M,E, P, allValuesFrom(PX,DX)) :- 2604 use_owl(M,E, 'owl:allValuesFrom',D,allValuesFrom(E,P)), 2605 ( owl_description(M,D, DX) ; owl_datarange(M,D,DX)), 2606 ( P = [_|_], owl_property_list(M,P,PX) ; owl_property_expression(M,P, PX)). 2607 2608 2609% changed from thea value-->hasValue 2610owl_restriction_type(M,E, P, hasValue(PX,Value)) :- 2611 use_owl(M,E, 'owl:hasValue',Value,hasValue(E)), 2612 owl_property_expression(M,P, PX). 2613 2614% VV:check if RDF parser returns a triple with O=true for 2615owl_restriction_type(M,E, P, hasSelf(PX)) :- 2616 use_owl(M,E, 'owl:hasSelf', true,hasSelf(E)), 2617 owl_property_expression(M,P, PX). 2618 2619% Support of deprecated translations: 2620% in the OWL2 RDF mapping, unqualified CRs use owl:{min,max}Cardinality 2621% and QCQs use owl:{min,ax}QualifiedCardinality 2622% 2623% however, there appear to be some ontologies; e.g. Hydrology.owl. 2624% that use an older mapping, where the same properties are used 2625% for QCR and unqCR 2626% 2627% it is relatively easy to support this legacy ontologies; however 2628% we must process these BEFORE unqualified cardinality restrictions. 2629 2630owl_restriction_type(M,E, P, exactCardinality(N,PX,DX)) :- 2631 test_use_owl(M,E, 'owl:cardinality',Lit), 2632 onClass(M,E,D), 2633 owl_description(M,D, DX),!, 2634 use_owl(M,E, 'owl:cardinality',Lit,cardinality(E)), 2635 literal_integer(Lit,N), 2636 owl_property_expression(M,P, PX). 2637 2638owl_restriction_type(M,E, P, minCardinality(N,PX,DX)) :- 2639 test_use_owl(M,E, 'owl:minCardinality',Lit), 2640 ( onClass(M,E,D),owl_description(M,D, DX) 2641 ; onDataRange(M,E,D), owl_datarange(M,D,DX)), 2642 !, 2643 % we are sure this is an old-style unqualified CR - now consume triples 2644 use_owl(M,E, 'owl:minCardinality',Lit,minCardinality(E)), 2645 literal_integer(Lit,N), 2646 owl_property_expression(M,P, PX). 2647 2648owl_restriction_type(M,E, P, maxCardinality(N,PX,DX)) :- 2649 test_use_owl(M,E, 'owl:maxCardinality',Lit), 2650 ( onClass(M,E,D),owl_description(M,D, DX) 2651 ; onDataRange(M,E,D), owl_datarange(M,D,DX)), 2652 !, 2653 % we are sure this is an old-style unqualified CR - now consume triples 2654 use_owl(M,E, 'owl:maxCardinality',Lit,maxCard(E)), 2655 literal_integer(Lit,N), 2656 owl_property_expression(M,P, PX). 2657 2658% END OF Support of deprecated translations: 2659 2660% the following are all in the spec: 2661 2662% changed from Thea1->2: cardinality->exactCardinality 2663owl_restriction_type(M,E, P,exactCardinality(N,PX)) :- 2664 use_owl(M,E, 'owl:cardinality',Lit,cardinality(E)), 2665 literal_integer(Lit,N), 2666 owl_property_expression(M,P, PX). 2667 2668owl_restriction_type(M,E, P,exactCardinality(N,PX,DX)) :- 2669 use_owl(M,E, 'owl:qualifiedCardinality',Lit),literal_integer(Lit,N), 2670 ( onClass(M,E,D),owl_description(M,D, DX) ; 2671 onDataRange(M,E,D), owl_datarange(M,D,DX) 2672 ), 2673 owl_property_expression(M,P, PX). 2674 2675 2676owl_restriction_type(M,E, P, minCardinality(N,PX)) :- 2677 use_owl(M,E, 'owl:minCardinality',Lit,cardinality(E)),literal_integer(Lit,N), 2678 owl_property_expression(M,P, PX). 2679 2680owl_restriction_type(M,E, P, minCardinality(N,PX,DX)) :- 2681 use_owl(M,E, 'owl:minQualifiedCardinality',Lit,cardinality(E)),literal_integer(Lit,N), 2682 ( onClass(M,E,D),owl_description(M,D, DX); 2683 onDataRange(M,E,D), owl_datarange(M,D,DX) 2684 ), 2685 owl_property_expression(M,P, PX). 2686 2687 2688owl_restriction_type(M,E, P, maxCardinality(N,PX)) :- 2689 use_owl(M,E, 'owl:maxCardinality',Lit,maxCardinality(E)),literal_integer(Lit,N), 2690 owl_property_expression(M,P, PX). 2691 2692owl_restriction_type(M,E, P, maxCardinality(N,PX,DX)) :- 2693 use_owl(M,E, 'owl:maxQualifiedCardinality',Lit,cardinality(E,Lit)), 2694 literal_integer(Lit,N), 2695 ( onClass(M,E,D),owl_description(M,D, DX); 2696 onDataRange(M,E,D), owl_datarange(M,D,DX)), 2697 owl_property_expression(M,P, PX). 2698 2699 2700% Table 14. Parsing of Data Ranges for Compatibility with OWL DL 2701% Included into owl_datarange clauses above 2702 2703% Table 15. Parsing of Class Expressions for Compatibility with OWL DL 2704% Included into owl_dexcription clauses above 2705 2706% Table 16. Parsing of Axioms without Annotations 2707% Declarations handled previously 2708% CLASS AXIOMS 2709% valid_axiom_annotation_mode: add clauses for the disjoint etc .... 2710 2711collect_r_nodes(M) :- 2712 retractall(M:axiom_r_node(_,_,_,_)), 2713 forall(( test_use_owl(M,Node,'rdf:type','owl:Axiom'), 2714 test_use_owl(M,Node,'owl:annotatedSource',S), 2715 test_use_owl(M,Node,'owl:annotatedProperty',P), 2716 test_use_owl(M,Node,'owl:annotatedTarget',O)), 2717 (assert(M:axiom_r_node(S,P,O,Node)), 2718 assert(M:owl(S,P,O,not_used)), 2719 debug(owl_parser_detail,'~w',[axiom_r_node(S,P,O,Node)]), 2720 use_owl(M,[owl(Node,'rdf:type','owl:Axiom'), 2721 owl(Node,'owl:annotatedSource',S), 2722 owl(Node,'owl:annotatedProperty',P), 2723 owl(Node,'owl:annotatedTarget',O)]))), 2724 2725 retractall(M:annotation_r_node(_,_,_,_)), 2726 forall(( test_use_owl(M,W,'rdf:type','owl:Annotation'), 2727 test_use_owl(M,W,'owl:annotatedSource',S), 2728 test_use_owl(M,W,'owl:annotatedProperty',P), 2729 test_use_owl(M,W,'owl:annotatedTarget',O)), 2730 (assert(M:annotation_r_node(S,P,O,Node)), 2731 debug(owl_parser_detail,'~w',[annotation_r_node(S,P,O,Node)]), 2732 use_owl(M,[owl(W,'rdf:type','owl:Annotation'), 2733 owl(W,'owl:annotatedSource',S), 2734 owl(W,'owl:annotatedProperty',P), 2735 owl(W,'owl:annotatedTarget',O)]))).
2742valid_axiom_annotation_mode(true,M,S,P,O,List) :- 2743 expand_ns(P,PE), 2744 findall(Node,M:axiom_r_node(S,PE,O,Node),List). 2745 2746valid_axiom_annotation_mode(false,_M,_S,_P,_O,[]). 2747 2748 2749owl_parse_axiom(M,subClassOf(DX,DY),AnnMode,List) :- 2750 test_use_owl(M,X,'rdfs:subClassOf',Y), 2751 valid_axiom_annotation_mode(AnnMode,M,X,'rdfs:subClassOf',Y,List), 2752 use_owl(M,X,'rdfs:subClassOf',Y,subclassOf(X,Y)), 2753 owl_description(M,X,DX), 2754 owl_description(M,Y,DY). 2755 2756% Process each equivalentClass pair separately in order to capture 2757% annotations. Block the maximally connected subgraph. 2758% TODO. Process the equivalent(L) axioms to generate maximally connected 2759% equivalentClasses(L) axioms. (but without annotations?) 2760 2761owl_parse_axiom(M,equivalentClasses(DL),AnnMode,List) :- 2762 test_use_owl(M,X,'owl:equivalentClass',Y), 2763 valid_axiom_annotation_mode(AnnMode,M,X,'owl:equivalentClass',Y,List), 2764 use_owl(M,X,'owl:equivalentClass',Y,equivalentClass(X,Y)), 2765 % maximally_connected_subgraph_over('owl:equivalentClass',L), 2766 maplist(owl_description(M),[X,Y],DL), 2767 debug(owl_parser_detail,'equivalentClasses Descs: ~w',[DL]). 2768 2769 2770owl_parse_axiom(M,equivalentClasses([C,intersectionOf(D)]),AnnMode,List) :- 2771 M:class(C), 2772 test_use_owl(M,C,'owl:intersectionOf',D1), 2773 debug(owl_parser,'equivalent collection; intersection for ~w',[C]), 2774 valid_axiom_annotation_mode(AnnMode,M,C,'owl:intersectionOf',D1,List), 2775 owl_description(M,C,intersectionOf(D)). 2776 2777owl_parse_axiom(M,equivalentClasses([C,unionOf(D)]),AnnMode,List) :- 2778 M:class(C), 2779 test_use_owl(M,C,'owl:unionOf',D1), 2780 debug(owl_parser,'equivalent collection; union for ~w',[C]), 2781 valid_axiom_annotation_mode(AnnMode,M,C,'owl:unionOf',D1,List), 2782 owl_description(M,C,unionOf(D)). 2783 2784owl_parse_axiom(M,equivalentClasses([C,oneOf(D)]),AnnMode,List) :- 2785 M:class(C), 2786 test_use_owl(M,C,'owl:oneOf',D1), 2787 debug(owl_parser,'equivalent collection; one of for ~w',[C]), 2788 valid_axiom_annotation_mode(AnnMode,M,C,'owl:oneOf',D1,List), 2789 owl_description(M,C,oneOf(D)). 2790 2791 2792owl_parse_axiom(M,equivalentClasses([C,D])) :- 2793 % TODO: this could be made more efficient by enforcing order of building 2794 ( test_use_owl(M,C,'rdf:type','owl:Class',named) 2795 ; test_use_owl(M,C,'rdf:type','rdfs:Class',named) 2796 ; M:class(C)), 2797 owl_description(M,C,D), 2798 C\=D. 2799 2800% TODO. Process the disjointClasses(L) axioms to generate 2801% larger set of disjoint: ie if N classes are pairwise DisJoint 2802% then we can assert a disjointClasses for all N 2803 2804owl_parse_axiom(M,disjointClasses([DX,DY]),AnnMode,List) :- 2805 test_use_owl(M,X,'owl:disjointWith',Y), 2806 valid_axiom_annotation_mode(AnnMode,M,X,'owl:disjointWith',Y,List), 2807 use_owl(M,X,'owl:disjointWith',Y,disjointWith(X,Y)), 2808 owl_description(M,X,DX), 2809 owl_description(M,Y,DY). 2810 2811% One of the cases where annotations are those of _x and we do not seek 2812% for further annotation axioms. Par. 3.2.5. 2813% Whatever the AnnNode, _x is returned (will be ignored if mode false 2814 2815owl_parse_axiom(M,disjointClasses(L),_AnnMode,[X]) :- 2816 % TODO: X may be referred to in an annotation axiom?? 2817 use_owl(M,X,'rdf:type','owl:AllDisjointClasses',allDisjointClasses(X)), 2818 use_owl(M,X,'owl:members',L1,members(L1)), 2819 owl_description_list(M,L1,L). 2820 2821 2822owl_parse_axiom(M,disjointUnion(DX,DY),AnnMode,List) :- 2823 test_use_owl(M,X,'owl:disjointUnionOf',Y), 2824 valid_axiom_annotation_mode(AnnMode,M,X,'owl:disjointUnionOf',Y,List), 2825 use_owl(M,X,'owl:disjointUnionOf',Y,disjointUnionOf(X,Y)), 2826 owl_description(M,X,DX), 2827 owl_description_list(M,Y,DY). 2828 2829 2830% PROPERTY AXIOMS 2831 2832 2833% introduces bnode 2834owl_parse_axiom(M,subPropertyOf(propertyChain(PL),QX),AnnMode,List) :- 2835 test_use_owl(M,Q,'owl:propertyChainAxiom',L1), 2836 valid_axiom_annotation_mode(AnnMode,M,Q,'owl:propertyChainAxiom',L1,List), 2837 use_owl(M,Q,'owl:propertyChainAxiom',L1,propertyChainAxiom(Q)), 2838 owl_property_list(M,L1,PL), 2839 owl_property_expression(M,Q,QX). 2840 2841owl_parse_axiom(M,subPropertyOf(PX,QX),AnnMode,List) :- 2842 test_use_owl(M,P,'rdfs:subPropertyOf',Q), 2843 valid_axiom_annotation_mode(AnnMode,M,P,'rdfs:subPropertyOf',Q,List), 2844 use_owl(M,P,'rdfs:subPropertyOf',Q,subPropertyOf(P,Q)), 2845 owl_property_expression(M,P,PX), 2846 owl_property_expression(M,Q,QX). 2847 2848 2849% Process each equivalentProperty pair separately in order to capture 2850% annotations. Block the maximally connected subgraph. 2851% TODO. Process the equivalent(L) axioms to generate maximally connected 2852% equivalentProperties(L) axioms. (but without annotations?) 2853 2854owl_parse_axiom(M,equivalentProperties(OPEL),AnnMode,List) :- 2855 test_use_owl(M,X,'owl:equivalentProperty',Y), 2856 valid_axiom_annotation_mode(AnnMode,M,X,'owl:equivalentProperty',Y,List), 2857 use_owl(M,X,'owl:equivalentProperty',Y,equivProperty(X,Y)), 2858 % maximally_connected_subgraph_over('owl:equivalentProperty',L), 2859 maplist(owl_property_expression(M),[X,Y],OPEL). 2860 2861 2862% TODO. Process the disjointProperties(L) axioms to generate 2863% larger set of disjoint: ie if N properties are pairwise DisJoint 2864% then we can assert a disjointClasses for all N 2865 2866owl_parse_axiom(M,disjointProperties([DX,DY]),AnnMode,List) :- 2867 test_use_owl(M,X,'owl:propertyDisjointWith',Y), 2868 valid_axiom_annotation_mode(AnnMode,M,X,'owl:propertyDisjointWith',Y,List), 2869 use_owl(M,X,'owl:propertyDisjointWith',Y,propertyDisjointWith(X,Y)), 2870 owl_description(M,X,DX), 2871 owl_description(M,Y,DY). 2872 2873% One more of the cases where annotations are those of _x and we do not 2874% seek for further annotation axioms. Par. 3.2.5. Whatever the AnnNode, 2875% _x is returned (will be ignored if mode false) 2876 2877owl_parse_axiom(M,disjointProperties(L),_AnnMode,[X]) :- 2878 % TODO: X may be referred to in an annotation axiom?? 2879 use_owl(M,X,'rdf:type','owl:AllDisjointProperties',allDisjointProps(X,L1)), 2880 use_owl(M,X,'owl:members',L1,members(L1)), 2881 L1 = [_,_|_], % length >= 2 2882 owl_property_list(M,L1,L). 2883 2884 2885owl_parse_axiom(M,propertyDomain(PX,CX),AnnMode,List) :- 2886 test_use_owl(M,P,'rdfs:domain',C), 2887 valid_axiom_annotation_mode(AnnMode,M,P,'rdfs:domain',C,List), 2888 use_owl(M,P,'rdfs:domain',C,domain(P,C)), 2889 ( M:annotationProperty(P),CX = C ; 2890 owl_property_expression(M,P,PX), 2891 owl_description(M,C,CX) 2892 ). 2893 2894% We need to distinguish here between object and data property 2895% Currently we first test if the range is a class, this means OPE 2896% otherwise if it is a datarange it means a DPE. 2897% Ideally we should also check possible declarations of OPE or DPE. 2898 2899owl_parse_axiom(M,propertyRange(PX,CX),AnnMode,List) :- 2900 test_use_owl(M,P,'rdfs:range',C), 2901 valid_axiom_annotation_mode(AnnMode,M,P,'rdfs:range',C,List), 2902 use_owl(M,P,'rdfs:range',C,range(P,C)), 2903 ( M:annotationProperty(P) -> PX = P, CX = C ; 2904 owl_property_expression(M,P,PX), 2905 ( owl_description(M,C,CX) -> true ; owl_datarange(M,C,CX)) 2906 ). 2907 2908owl_parse_axiom(M,inverseProperties(PX,QX),AnnMode,List) :- 2909 test_use_owl(M,P,'owl:inverseOf',Q), 2910 valid_axiom_annotation_mode(AnnMode,M,P,'owl:inverseOf',Q,List), 2911 use_owl(M,P,'owl:inverseOf',Q,inverseOf(P,Q)), 2912 owl_property_expression(M,P,PX), 2913 owl_property_expression(M,Q,QX). 2914 2915owl_parse_axiom(M,functionalProperty(P),AnnMode,List) :- 2916 test_use_owl(M,P,'rdf:type','owl:FunctionalProperty'), 2917 valid_axiom_annotation_mode(AnnMode,M,P,'rdf:type','owl:FunctionalProperty',List), 2918 use_owl(M,P,'rdf:type','owl:FunctionalProperty',functionalProperty(P)). 2919 2920owl_parse_axiom(M,inverseFunctionalProperty(P),AnnMode,List) :- 2921 test_use_owl(M,P,'rdf:type','owl:InverseFunctionalProperty'), 2922 valid_axiom_annotation_mode(AnnMode,M,P,'rdf:type','owl:InverseFunctionalProperty',List), 2923 use_owl(M,P,'rdf:type','owl:InverseFunctionalProperty',inverseFunctionalProperty(P)). 2924 2925owl_parse_axiom(M,reflexiveProperty(P),AnnMode,List) :- 2926 test_use_owl(M,P,'rdf:type','owl:ReflexiveProperty'), 2927 valid_axiom_annotation_mode(AnnMode,M,P,'rdf:type','owl:ReflexiveProperty',List), 2928 use_owl(M,P,'rdf:type','owl:ReflexiveProperty',reflexiveProperty(P)). 2929 2930owl_parse_axiom(M,irreflexiveProperty(P),AnnMode,List) :- 2931 test_use_owl(M,P,'rdf:type','owl:IrreflexiveProperty'), 2932 valid_axiom_annotation_mode(AnnMode,M,P,'rdf:type','owl:IrreflexiveProperty',List), 2933 use_owl(M,P,'rdf:type','owl:IrreflexiveProperty',irreflexiveProperty(P)). 2934 2935owl_parse_axiom(M,symmetricProperty(P),AnnMode,List) :- 2936 test_use_owl(M,P,'rdf:type','owl:SymmetricProperty'), 2937 valid_axiom_annotation_mode(AnnMode,M,P,'rdf:type','owl:SymmetricProperty',List), 2938 use_owl(M,P,'rdf:type','owl:SymmetricProperty',symmetricProperty(P)). 2939 2940owl_parse_axiom(M,asymmetricProperty(P),AnnMode,List) :- 2941 test_use_owl(M,P,'rdf:type','owl:AsymmetricProperty'), 2942 valid_axiom_annotation_mode(AnnMode,M,P,'rdf:type','owl:AsymmetricProperty',List), 2943 use_owl(M,P,'rdf:type','owl:AsymmetricProperty',assymetricProperty(P)). 2944 2945owl_parse_axiom(M,transitiveProperty(P),AnnMode,List) :- 2946 test_use_owl(M,P,'rdf:type','owl:TransitiveProperty'), 2947 valid_axiom_annotation_mode(AnnMode,M,P,'rdf:type','owl:TransitiveProperty',List), 2948 use_owl(M,P,'rdf:type','owl:TransitiveProperty',transitiveProperty(P)). 2949 2950owl_parse_axiom(M,hasKey(CX,L),AnnMode,List) :- 2951 test_use_owl(M,C,'owl:hasKey',L1), 2952 valid_axiom_annotation_mode(AnnMode,M,C,'owl:hasKey',L1,List), 2953 use_owl(M,C,'owl:hasKey',L1,hasKey(C)), 2954 owl_description(M,C,CX), 2955 L1 = [_,_|_], % length >= 2 2956 owl_property_list(M,L1,L). 2957 2958% INDIVIDUALS 2959 2960owl_parse_axiom(M,sameIndividual([X,Y]),AnnMode,List) :- 2961 test_use_owl(M,X,'owl:sameAs',Y), 2962 valid_axiom_annotation_mode(AnnMode,M,X,'owl:sameAs',Y,List), 2963 use_owl(M,X,'owl:sameAs',Y,sameAs(X,Y)). 2964 2965owl_parse_axiom(M,differentIndividuals([X,Y]),AnnMode,List) :- 2966 test_use_owl(M,X,'owl:differentFrom',Y), 2967 valid_axiom_annotation_mode(AnnMode,M,X,'owl:differentFrom',Y,List), 2968 use_owl(M,X,'owl:differentFrom',Y,differentFrom(X,Y)). 2969 2970owl_parse_axiom(M,differentIndividuals(L),_AnnMode,[X]) :- 2971 use_owl(M,X,'rdf:type','owl:AllDifferent',allDifferent(L)), 2972 use_owl(M,X,'owl:distinctMembers',L1,distinctMembers(L)), 2973 owl_individual_list(M,L1,L). 2974 2975owl_parse_axiom(M,differentIndividuals(L),_AnnMode,[X]) :- 2976 use_owl(M,X,'rdf:type','owl:AllDifferent',allDifferent(X)), 2977 use_owl(M,X,'owl:members',L1,members(L)), 2978 owl_individual_list(M,L1,L). 2979 2980% make sure this is done before fetching classAssertion/2; 2981% -- the annotationAssertion matching clause should preceded the classAssertion/2 matching clause 2982owl_parse_axiom(M,annotationAssertion('owl:deprecated', X, true),AnnMode,List) :- 2983 test_use_owl(M,X, 'rdf:type', 'owl:DeprecatedClass'), 2984 valid_axiom_annotation_mode(AnnMode,M,X,'rdf:type','owl:DeprecatedClass',List), 2985 use_owl(M,X, 'rdf:type', 'owl:DeprecatedClass',deprecatedClass(X)). 2986 2987% make sure this is done before fetching propertyAssertion/3 2988% this clause should precede it 2989owl_parse_axiom(M,annotationAssertion('owl:deprecated', X, true),AnnMode,List) :- 2990 test_use_owl(M,X, 'rdf:type', 'owl:DeprecatedProperty'), 2991 valid_axiom_annotation_mode(AnnMode,M,X,'rdf:type','owl:DeprecatedProperty',List), 2992 use_owl(M,X, 'rdf:type', 'owl:DeprecatedProperty',deprecatedProperty(X)). 2993 2994% Table 17. Parsing of Annotated Axioms 2995 2996dothislater(annotationAssertion/3). 2997% TODO - only on unnannotated pass? 2998% 2999 3000owl_parse_axiom(M,annotationAssertion(P,A,B),AnnMode,List) :- 3001 M:annotationProperty(P), 3002 test_use_owl(M,A,P,B), % B can be literal or individual 3003 valid_axiom_annotation_mode(AnnMode,M,A,P,B,List), 3004 use_owl(M,A,P,B,annotationProperty(P)). 3005 3006 3007dothislater(classAssertion/2). 3008owl_parse_axiom(M,classAssertion(CX,X),AnnMode,List) :- 3009 test_use_owl(M,X,'rdf:type',C), 3010 C\='http://www.w3.org/2002/07/owl#DeprecatedClass', 3011 % note: some ontologies may include a rdf:type with no 3012 % explicit class declaration. See testfiles/test_undeclared.owl 3013 %class(C), 3014 valid_axiom_annotation_mode(AnnMode,M,X,'rdf:type',C,List), 3015 use_owl(M,X,'rdf:type',C,classAssertion(CX,X)), 3016 % I added this to avoid class assertions for bNodes. Perhaps a better 3017 % way is to simply consume the owl4/ triple at the time of translating 3018 % the description? --CJM 3019 C\='http://www.w3.org/2002/07/owl#Class', 3020 % 3021 C\='http://www.w3.org/1999/02/22-rdf-syntax-ns#Property', 3022 owl_description(M,C,CX). 3023 3024dothislater(propertyAssertion/3). 3025owl_parse_axiom(M,propertyAssertion(PX,A,BX),AnnMode,List) :- 3026 test_use_owl(M,A,P,B), % B can be literal or individual 3027 P\='http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 3028 % note: some ontologies may include a triples with no 3029 % explicit property declaration. See testfiles/test_undeclared.owl 3030 %property(P), 3031 valid_axiom_annotation_mode(AnnMode,M,A,P,B,List), 3032 \+ M:annotationProperty(P), % these triples should have been removed before, during ann parsing 3033 owl_property_expression(M,P,PX), % can also be inverse 3034 % next line added by VV 9/3/2011 for Jochem Liem to support ID-lists as PA objects 3035 ( owl_individual_list(M,B,BX) -> true ; BX = B), 3036 use_owl(M,A,P,B,propertyAssertion(PX,A,BX)). 3037 3038 3039owl_parse_axiom(M,negativePropertyAssertion(PX,A,B),_,X) :- 3040 use_owl(M,X,'rdf:type','owl:NegativePropertyAssertion',negPropertyAssertion(PX,A,B)), 3041 use_owl(M,X,'owl:sourceIndividual',A,negPropertyAssertion(PX,A,B)), 3042 use_owl(M,X,'owl:assertionProperty',P,negPropertyAssertion(PX,A,B)), 3043 use_owl(M,X,'owl:targetValue',B,negPropertyAssertion(PX,A,B)), 3044 owl_property_expression(M,P,PX). 3045 3046 3047% process hooks; SWRL etc 3048 3049% Parsing annotationAssertions 3050% 3051 3052parse_annotation_assertions(M) :- 3053 ( M:trdf_setting(rind,RIND) -> true ; RIND = []),!, 3054 forall((M:aNN(X,AP,AV),findall( aNN(annotation(X,AP,AV),AP1,AV1), 3055 M:aNN(annotation(X,AP,AV),AP1,AV1),ANN), \+member(X,RIND), atomic(X), \+name(X,[95, 58, 68, 101, 115, 99, 114, 105, 112, 116, 105, 111, 110|_])), 3056 ( assert_axiom(M,annotationAssertion(AP,X,AV)), 3057 % VV 10/3/2010 keep annotation/3 3058 % retract(annotation(X,AP,AV)), 3059 forall(member(aNN(_,AP1,AV1),ANN), 3060 assert_axiom(M,annotation(annotationAssertion(AP,X,AV),AP1,AV1)) 3061 ) 3062 ) 3063 ), 3064 % forall(aNN(X,Y,Z),assert(annotation(X,Y,Z))), VV remove 25/1/11 3065 % annotation/3 axioms created already during owl_parse_annotated_axioms/1 3066 retractall(M:aNN(_,_,_)). 3067 3068% Table 18. Parsing of Axioms for Compatibility with OWL DL 3069 3070owl_parse_compatibility_DL(M,equivalentClasses([CEX,complementOf(CEY)])) :- 3071 use_owl(M,X,'owl:complementOf',Y,eq_classes), 3072 owl_description(M,X,CEX), 3073 owl_description(M,Y,CEY). 3074 3075 3076owl_parse_compatibility_DL(M,equivalentClasses([CEX,CEY])) :- 3077 use_owl(M,X,'owl:unionOf',Y,eq_classes), 3078 owl_description(M,X,CEX), 3079 owl_description_list(M,Y,DL), 3080 ( DL = [] -> CEY = 'owl:Nothing' ; (DL=[CEY]->true;CEY = unionOf(DL))). 3081 3082owl_parse_compatibility_DL(M,equivalentClasses([CEX,CEY])) :- 3083 use_owl(M,X,'owl:intersectionOf',Y,eq_classes), 3084 owl_description(M,X,CEX), 3085 owl_description_list(M,Y,DL), 3086 ( DL = [] -> CEY = 'owl:Thing' ; (DL=[CEY]->true;CEY = intersectionOf(DL))). 3087 3088owl_parse_compatibility_DL(M,equivalentClasses([CEX,CEY])) :- 3089 use_owl(M,X,'owl:oneOf',Y,eq_classes), 3090 owl_description(M,X,CEX), 3091 owl_description_list(M,Y,DL), 3092 ( DL = [] -> CEY = 'owl:Nothing' ; CEY = oneOf(DL)). 3093 3094% UTIL
3097maximally_connected_subgraph_over(P,CSet):-
3098 maximally_connected_subgraph_over(P,[],CSetL),
3099 member(CSet,CSetL).
3102maximally_connected_subgraph_over(P,Used,[CSet|All]):- 3103 test_use_owl(M,X,P,Y), % seed 3104 \+ member(X,Used), 3105 \+ member(Y,Used), 3106 use_owl(M,X,P,Y,maximally_conected), % seed 3107 !, 3108 extend_set_over(P,[X,Y],CSet), 3109 append(CSet,Used,Used2), 3110 maximally_connected_subgraph_over(P,Used2,All). 3111maximally_connected_subgraph_over(_,_,[]). 3112 3113 3114% det 3115extend_set_over(P,L,L2):- 3116 member(X,L), 3117 test_use_owl(M,X,P,Y), 3118 \+ member(Y,L), 3119 use_owl(M,X,P,Y,extend_set_over), 3120 !,extend_set_over(P,[Y|L],L2). 3121extend_set_over(P,L,L2):- 3122 member(X,L), 3123 test_use_owl(M,Y,P,X), 3124 \+ member(Y,L), 3125 use_owl(M,Y,P,X,extend_set_over), 3126 !,extend_set_over(P,[Y|L],L2). 3127extend_set_over(_,L,L):- !. 3128 3129literal_integer(literal(type,A),N) :- atom_number(A,N). 3130literal_integer(literal(type(_,A)),N) :- atom_number(A,N).
3134time_goal(Goal,Time):- 3135 statistics(cputime,T1), , 3136 statistics(cputime,T2), Time is T2-T1. 3137 3138timed_forall(Cond,Action) :- 3139 forall(Cond, 3140 ( time_goal(Action,Time), 3141 debug(owl2_bench,'Goal: ~w Time:~w',[Action,Time]))).
:- use_module(bio(owl2_from_rdf)). %
The file owl2_from_rdf.plt has some examples */
3156%:- thread_local ns4query/1.
3164load_owl(String):-
3165 get_module(M),
3166 retractall(M:ns4query(_)),
3167 open(String,read,S),
3168 load_owl_from_stream(S),!.
3176load_owl_from_string(String):- 3177 open_chars_stream(String,S), 3178 load_owl_from_stream(S). 3179 3180load_owl_from_stream(S):- 3181 get_module(M), 3182 retractall(M:trdf_setting(_,_)), 3183 process_rdf(stream(S), assert_list(M), [namespaces(NSList)]), 3184 close(S), 3185 trill:add_kb_prefixes(M:NSList), 3186 rdf_2_owl(M,'ont'), 3187 utility_translation_init(M), 3188 owl_canonical_parse_3(M,['ont']), 3189 parse_probabilistic_annotation_assertions(M). 3190 3191% Get the KB's prefixes contained into ns4query 3192:- multifile trill:kb_prefixes/1. 3193 3194trillkb_prefixes(M:L):- 3195 M:ns4query(L),!. 3196 3197% Adds a list of kb prefixes into ns4query 3198:- multifile trill:add_kb_prefixes/1. 3199 3200trilladd_kb_prefixes(_:[]):-!. 3201 3202trilladd_kb_prefixes(M:[(H=H1)|T]):- 3203 trill:add_kb_prefix(M:H,H1), 3204 trill:add_kb_prefixes(M:T). 3205 3206% Adds a prefix into ns4query 3207:- multifile trill:add_kb_prefix/2. 3208 3209trilladd_kb_prefix(M:'',B):- !, 3210 trill:add_kb_prefix(M:[],B). 3211 3212trilladd_kb_prefix(M:A,B):- 3213 M:ns4query(L),!, 3214 (\+ member((A=_),L) -> 3215 (retract(M:ns4query(L)), 3216 append(L,[(A=B)],NL), 3217 assert(M:ns4query(NL)) 3218 ) 3219 ; 3220 true 3221 ). 3222 3223trilladd_kb_prefix(M:A,B):- 3224 assert(M:ns4query([(A=B)])). 3225 3226% Removes a prefix from ns4query 3227:- multifile trill:remove_kb_prefix/2. 3228trillremove_kb_prefix(M:A,B):- 3229 M:ns4query(L),!, 3230 (member((A=B),L) -> 3231 (retract(M:ns4query(L)), 3232 delete(L,(A=B),NL), 3233 assert(M:ns4query(NL)) 3234 ) 3235 ; 3236 true 3237 ). 3238 3239:- multifile trill:remove_kb_prefix/1. 3240trillremove_kb_prefix(M:A):- 3241 M:ns4query(L),!, 3242 (member((A=B),L) *-> 3243 (retract(M:ns4query(L)), 3244 delete(L,(A=B),NL), 3245 assert(M:ns4query(NL)) 3246 ) 3247 ; 3248 (member((B=A),L),! *-> 3249 (retract(M:ns4query(L)), 3250 delete(L,(B=A),NL), 3251 assert(M:ns4query(NL)) 3252 ) 3253 ; 3254 true 3255 ) 3256 ). 3257 3258 3259assert_list(_M,[], _):-!. 3260assert_list(M,[H|T], Source) :- 3261 %H=..[_|Args], 3262 %H1=..[rdf|Args], 3263 assert(M:), 3264 %add_atoms_from_axiom(M,Args), 3265 assert_list(M,T, Source). 3266 3267find_all_probabilistic_annotations(M,An,Ax,PV):- 3268 M:annotation(Ax,An,literal(lang(_Lang, PV))), 3269 atom(PV). 3270 3271find_all_probabilistic_annotations(M,An,Ax,PV):- 3272 M:annotation(Ax,An,literal(type(_Type, PV))), 3273 atom(PV). 3274 3275find_all_probabilistic_annotations(M,An,Ax,PV):- 3276 M:annotation(Ax,An,literal(PV)), 3277 atom(PV). 3278 3279 3280parse_probabilistic_annotation_assertions(M) :- 3281 forall(find_all_probabilistic_annotations(M,An,Ax,PV), 3282 (assert_axiom(M,annotationAssertion(An,Ax,literal(PV)))) 3283 ), 3284 % forall(aNN(X,Y,Z),assert(annotation(X,Y,Z))), VV remove 25/1/11 3285 % annotation/3 axioms created already during owl_parse_annotated_axioms/1 3286 retractall(M:annotation(_,_,_)). 3287 3288/* 3289query_is([Q|_],0,Q):-!. 3290query_is([_|T],N,Q):- 3291 NN is N - 1, 3292 query_is(T,NN,Q). 3293 3294set_new_query([_|T],0,NQ,[NQ|T]):-!. 3295set_new_query([Q|T],N,NQ,[Q|NT]):- 3296 NN is N - 1, 3297 set_new_query(T,NN,NQ,NT). 3298 3299 3300query_expand(CQ):- 3301 CQ =.. [CQP | CQArgs], 3302 member((CQP,PosQ),[(aggregate_all,1), (limit,1)]),!, 3303 query_is(CQArgs,PosQ,Q), 3304 Q =.. [P|Args], 3305 get_module(M), 3306 M:ns4query(NSList),!, 3307 %retract(M:ns4query(NSList)), 3308 expand_all_ns(M,Args,NSList,NewArgs),!, 3309 NQ =.. [P|NewArgs], 3310 set_new_query(CQArgs,PosQ,NQ,CQNewArgs), 3311 NCQ =.. [CQP|CQNewArgs], 3312 call(NCQ). 3313 3314query_expand(Q):- 3315 Q =.. [P|Args], 3316 get_module(M), 3317 M:ns4query(NSList),!, 3318 %retract(M:ns4query(NSList)), 3319 expand_all_ns(M,Args,NSList,NewArgs),!, 3320 NQ =.. [P|NewArgs], 3321 call(NQ). 3322*/ 3323 3324 3325 3326expand_argument(M,literal(P),NSList,ExpP) :- !, 3327 expand_literal(M,literal(P),NSList,ExpP). 3328expand_argument(M,P,NSList,ExpP) :- 3329 (expand_classExpression(M,P,NSList,ExpP) ; 3330 expand_individual(M,P,NSList,ExpP) ; 3331 expand_propertyExpression(M,P,NSList,ExpP) ; 3332 expand_axiom(M,P,NSList,ExpP) ; 3333 expand_annotationProperty(M,P,NSList,ExpP) ; 3334 expand_dataRange(M,P,NSList,ExpP) ; 3335 expand_ontology(M,P,NSList,ExpP) ), !.
3346expand_all_ns(M,Args,NSList,ExpandedArgs):-
3347 expand_all_ns(M,Args,NSList,true,ExpandedArgs).
3356expand_all_ns(_M,[],_,_,[]):- !. 3357 3358expand_all_ns(M,[P|T],NSList,AddName,[PNewArgs|NewArgs]):- 3359 is_list(P),!, 3360 expand_all_ns(M,P,NSList,AddName,PNewArgs), 3361 expand_all_ns(M,T,NSList,AddName,NewArgs). 3362 3363expand_all_ns(M,[P|T],NSList,AddName,[NP|NewArgs]):- 3364 expand_argument(M,P,NSList,NP), 3365 expand_all_ns(M,T,NSList,AddName,NewArgs). 3366 3367/* 3368expand_all_ns(M,[P|T],NSList,AddName,[NP|NewArgs]):- 3369 compound(P), 3370 P =.. [N | Args],!, 3371 expand_all_ns(M,Args,NSList,AddName,NewPArgs), 3372 NP =.. [N| NewPArgs], 3373 expand_all_ns(M,T,NSList,AddName,NewArgs). 3374 3375expand_all_ns(M,[H|T],NSList,AddName,[H|NewArgs]):- 3376 check_query_arg(M,H),!, 3377 expand_all_ns(M,T,NSList,AddName,NewArgs). 3378 3379expand_all_ns(M,[H|T],NSList,AddName,[NewArg|NewArgs]):- 3380 expand_ns4query(M,H,NSList,AddName,NewArg), 3381 expand_all_ns(M,T,NSList,AddName,NewArgs). 3382 3383check_query_arg(M,Arg) :- 3384 atomic(Arg),!, 3385 trill:axiom(M:Ax), 3386 in_axiom(Arg,[Ax]),!, 3387 add_kb_atom(M,Arg). 3388 3389expand_ns4query(M,NS_URL,NSList,AddName, Full_URL):- 3390 nonvar(NS_URL), 3391 NS_URL \= literal(_), 3392 uri_split(NS_URL,Short_NS,Term, ':'), 3393 member((Short_NS=Long_NS),NSList), 3394 concat_atom([Long_NS,Term],Full_URL),!, 3395 ( AddName == true *-> add_kb_atom(M,Full_URL) ; true). 3396 3397expand_ns4query(M,NS_URL,NSList,AddName, Full_URL):- 3398 nonvar(NS_URL), 3399 NS_URL \= literal(_), 3400 \+ sub_atom(NS_URL,_,_,_,':'), 3401 member(([]=Long_NS),NSList), 3402 concat_atom([Long_NS,NS_URL],Full_URL),!, 3403 ( AddName == true *-> add_kb_atom(M,Full_URL) ; true). 3404 3405expand_ns4query(_M,URL,_,_,URL). 3406*/ 3407/* 3408expand_ns4query(_M,URL,_,_,URL):- 3409 var(URL),!. 3410*/ 3411 3412% check whether the given atom is present in an axiom 3413in_axiom(Atom,[Atom|_]):- !. 3414 3415in_axiom(Atom,[literal(_)|T]):-!, 3416 in_axiom(Atom,T). 3417 3418in_axiom(Atom,[Axiom|_]):- 3419 is_list(Axiom), 3420 in_axiom(Atom,Axiom),!. 3421 3422 3423in_axiom(Atom,[Axiom|_]):- 3424 \+ is_list(Axiom), 3425 compound(Axiom), 3426 Axiom=..[_|Args], 3427 in_axiom(Atom,Args),!. 3428 3429in_axiom(Atom,[_|T]):- 3430 in_axiom(Atom,T). 3431 3432% save atoms in kb for checking existence when querying 3433add_atoms_from_axiom(_M,[]):-!. 3434 3435add_atoms_from_axiom(M,[H|T]):- 3436 compound(H), 3437 H =.. ['literal' | _],!, 3438 add_atoms_from_axiom(M,T). 3439 3440add_atoms_from_axiom(M,[H|T]):- 3441 compound(H), 3442 H =.. [_N, Args],!, 3443 ( is_list(Args) -> 3444 add_atoms_from_axiom(M,Args) 3445 ; 3446 add_atoms_from_axiom(M,[Args]) 3447 ), 3448 add_atoms_from_axiom(M,T). 3449 3450add_atoms_from_axiom(M,[H|T]):- 3451 compound(H), 3452 H =.. [_N | Args],!, 3453 add_atoms_from_axiom(M,Args), 3454 add_atoms_from_axiom(M,T). 3455 3456add_atoms_from_axiom(M,[H|T]):- 3457 add_kb_atom(M,H),!, 3458 add_atoms_from_axiom(M,T). 3459 3460 3461add_kb_atom(M,IRI):- 3462 M:kb_atom(L), 3463 ( (member(IRI,L),!) *-> 3464 true 3465 ; 3466 (retract(M:kb_atom(_)), 3467 assert(M:kb_atom([IRI|L])) 3468 ) 3469 ). 3470 3471 3472add_kb_atoms(_M,_Type,[]):-!. 3473 3474add_kb_atoms(M,Type,[H|T]):- 3475 M:kb_atom(KBA0), 3476 L=KBA0.Type, 3477 ( memberchk(H,L) -> 3478 true 3479 ; 3480 ( retractall(M:kb_atom(_)), 3481 KBA=KBA0.put(Type,[H|L]), 3482 assert(M:kb_atom(KBA)) 3483 ) 3484 ), 3485 add_kb_atoms(M,Type,T). 3486 3487% TODO remove this => dataproperty always as dataproperty, object property as property (for retrocompatibility) or objectproperty 3488fix_wrongly_classified_atoms(M):- 3489 M:kb_atom(KBA0), 3490 findall(OP,M:objectProperty(OP),ObjPs), 3491 findall(DP,M:dataProperty(DP),DataPs), 3492 fix_wrongly_classified_properties(ObjPs,objectProperty,KBA0,KBA1), 3493 fix_wrongly_classified_properties(DataPs,dataProperty,KBA1,KBA2), 3494 fix_duplicated_wrongly_classified_properties(KBA2.objectProperty,KBA2.dataProperty,KBA2,KBA), 3495 retractall(M:kb_atom(_)), 3496 assert(M:kb_atom(KBA)). 3497 3498fix_wrongly_classified_properties([],_Type,KBA,KBA). 3499 3500fix_wrongly_classified_properties([H|T],Type,KBA0,KBA):- 3501 RP=KBA0.Type, 3502 ( Type=objectProperty -> OtherType=dataProperty ; OtherType=objectProperty ), 3503 WP=KBA0.OtherType, 3504 ( memberchk(H,RP) -> NRP=RP ; NRP=[H|RP] ), 3505 ( memberchk(H,WP) -> delete(WP,H,NWP) ; NWP=WP ), 3506 KBA1=KBA0.put(Type,NRP), 3507 KBA2=KBA1.put(OtherType,NWP), 3508 fix_wrongly_classified_properties(T,Type,KBA2,KBA). 3509 3510fix_duplicated_wrongly_classified_properties([],_DP,KBA,KBA). 3511 3512fix_duplicated_wrongly_classified_properties([H|T],DP,KBA0,KBA):- 3513 memberchk(H,DP),!, 3514 delete(DP,H,NDP), 3515 KBA1=KBA0.put(dataProperty,NDP), 3516 fix_duplicated_wrongly_classified_properties(T,DP,KBA1,KBA). 3517 3518fix_duplicated_wrongly_classified_properties([_H|T],DP,KBA0,KBA):- 3519 fix_duplicated_wrongly_classified_properties(T,DP,KBA0,KBA). 3520 3521 3522:- multifile trill:add_axiom/1. 3523trilladd_axiom(M:Ax):- 3524 assert(M:addKBName), 3525 %init_kb_atom(M), 3526 create_and_assert_axioms(M,Ax), 3527 retractall(M:addKBName), 3528 trill:update_tabs(M,Ax). 3529 3530:- multifile trill:add_axioms/1. 3531trilladd_axioms(_:[]). 3532 3533trilladd_axioms(M:[H|T]) :- 3534 trill:add_axiom(M:H), 3535 trill:add_axioms(M:T). 3536 3537:- multifile trill:remove_axiom/1. 3538trillremove_axiom(M:Ax):- 3539 %print_message(warning,under_development), 3540 ( M:ns4query(NSList) -> true; NSList = []), 3541 expand_axiom(M,Ax,NSList,ExpAx), 3542 retract_axiom(M,ExpAx), 3543 retractall(M:owl(ExpAx,'ont')),!, 3544 trill:reset_query. 3545 3546 3547/* 3548trill:remove_axiom(M:subClassOf(C,D)):- 3549 print_message(warning,under_development), 3550 ( M:ns4query(NSList) -> true; NSList = []), 3551 expand_axiom(M,subClassOf(C,D),NSList,subClassOf(ExpC,ExpD)), 3552 remove_subClassOf(M,ExpC,ExpD), 3553 retract_axiom(M,subClassOf(ExpC,ExpD)), 3554 retractall(M:owl(subClassOf(ExpC,ExpD),'ont')),!. 3555 3556trill:remove_axiom(M:Ax):- 3557 print_message(warning,under_development), 3558 ( M:ns4query(NSList) *-> true; NSList = []), 3559 Ax =.. [P|Args], 3560 ( (length(Args,1), Args = [IntArgs], is_list(IntArgs)) -> 3561 ( expand_all_ns(M,IntArgs,NSList,false,ArgsExp), 3562 AxEx =.. [P,ArgsExp] 3563 ) 3564 ; 3565 ( expand_all_ns(M,Args,NSList,false,ArgsExp), 3566 AxEx =.. [P|ArgsExp] 3567 ) 3568 ), 3569 retract_axiom(M,AxEx), 3570 retractall(M:owl(AxEx,'ont')),!. 3571*/ 3572 3573:- multifile trill:remove_axioms/1. 3574trillremove_axioms(_:[]):-!. 3575 3576trillremove_axioms(M:[H|T]) :- 3577 trill:remove_axiom(M:H), 3578 trill:remove_axioms(M:T). 3579 3580test_and_assert(M,Ax,O):- 3581 (\+ M:owl(Ax,O) -> 3582 (assert_axiom(M,Ax,O), assert(M:owl(Ax,O))) 3583 ; 3584 true 3585 ). 3586 3587get_module(M):- 3588 pengine_self(Self), 3589 pengine_property(Self,module(M)),!. 3590get_module(M):- !, 3591 prolog_load_context(module,M). 3592 3593parse_rdf_from_owl_rdf_pred(String):- 3594 open_chars_stream(String,S), 3595 load_owl_from_stream(S). 3596 3597/* 3598create_and_assert_axioms(M,Axiom) :- 3599 Axiom=..[P|Args], 3600 ( M:ns4query(NSList) -> true; NSList = []), 3601 ( (length(Args,1), Args = [IntArgs], is_list(IntArgs)) -> 3602 ( expand_all_ns(M,IntArgs,NSList,ArgsExp), 3603 ExpAxiom =.. [P,ArgsExp] 3604 ) 3605 ; 3606 ( expand_axiom(M,Axiom,NSList,ExpAxiom) 3607 %NewTRILLAxiom =.. [P|ArgsExp] 3608 ) 3609 ), 3610 test_and_assert(M,ExpAxiom,'ont'). 3611*/ 3612 3613create_and_assert_axioms(M,Axiom) :- 3614 ( M:ns4query(NSList) -> true; NSList = []), 3615 expand_axiom(M,Axiom,NSList,ExpAxiom), 3616 test_and_assert(M,ExpAxiom,'ont').
3624add_rule(M,max_rule):- !, 3625 M:rules(D,ND), 3626 ( memberchk(max_rule,ND) -> true ; 3627 ( retractall(M:rules(_,_)), 3628 assert(M:rules(D,[max_rule|ND])) 3629 ) 3630 ), !. 3631 3632add_rule(M,or_rule):- !, 3633 M:rules(D,ND), 3634 ( memberchk(or_rule,ND) -> true ; 3635 ( retractall(M:rules(_,_)), 3636 assert(M:rules(D,[or_rule|ND])) 3637 ) 3638 ), !. 3639 3640add_rule(M,Rule):- 3641 M:rules(D,ND), 3642 ( memberchk(Rule,D) -> true ; 3643 ( retractall(M:rules(_,_)), 3644 assert(M:rules([Rule|D],ND)) 3645 ) 3646 ), !.
expressivity(I,R)
-> I=1|2|3 (EL|ALC|S)
R=[0|1,0|1,0|1,0|1,0|1|2,0|1] ([H,R,O,I,N|Q,F])
/
3655add_expressivity(M,a):- 3656 M:expressivity(I,R), 3657 ( I > 1 ; ( retractall(M:expressivity(_,_)),assert(M:expressivity(2,R)))), !. 3658 3659add_expressivity(M,s):- 3660 M:expressivity(I,R), 3661 ( I > 2 ; ( retractall(M:expressivity(_,_)),assert(M:expressivity(3,R)))), !. 3662 3663add_expressivity(M,h):- 3664 M:expressivity(I,[H,R,O,I,Res,F]), 3665 ( H=1 ; ( retractall(M:expressivity(_,_)),assert(M:expressivity(I,[1,R,O,I,Res,F])))), !. 3666 3667add_expressivity(M,r):- 3668 M:expressivity(I,[H,R,O,I,Res,F]), 3669 ( R=1 ; ( retractall(M:expressivity(_,_)),assert(M:expressivity(I,[H,1,O,I,Res,F])))), !. 3670 3671add_expressivity(M,o):- 3672 M:expressivity(I,[H,R,O,I,Res,F]), 3673 ( O=1 ; ( retractall(M:expressivity(_,_)),assert(M:expressivity(I,[H,R,1,I,Res,F])))), !. 3674 3675add_expressivity(M,i):- 3676 M:expressivity(I,[H,R,O,I,Res,F]), 3677 ( I=1 ; ( retractall(M:expressivity(_,_)),assert(M:expressivity(I,[H,R,O,1,Res,F])))), !. 3678 3679add_expressivity(M,n):- 3680 M:expressivity(I,[H,R,O,I,Res,F]), 3681 ( Res>0 ; ( retractall(M:expressivity(_,_)),assert(M:expressivity(I,[H,R,O,I,1,F])))), !. 3682 3683add_expressivity(M,q):- 3684 M:expressivity(I,[H,R,O,I,Res,F]), 3685 ( Res>1 ; ( retractall(M:expressivity(_,_)),assert(M:expressivity(I,[H,R,O,I,2,F])))), !. 3686 3687add_expressivity(M,f):- 3688 M:expressivity(I,[H,R,O,I,Res,F]), 3689 ( F=1 ; ( retractall(M:expressivity(_,_)),assert(M:expressivity(I,[H,R,O,I,Res,1])))), !.
3697is_axiom(Axiom) :- 3698 functor(Axiom,Pred,Arity), 3699 axiompred(Pred/Arity),!. 3700 3701clean_up(M):- 3702 rdf_reset_db, 3703 M:(dynamic class/1, datatype/1, objectProperty/1, dataProperty/1, annotationProperty/1), 3704 M:(dynamic namedIndividual/1, anonymousIndividual/1, subClassOf/2, equivalentClasses/1, disjointClasses/1, disjointUnion/2), 3705 M:(dynamic subPropertyOf/2, equivalentProperties/1, disjointProperties/1, inverseProperties/2, propertyDomain/2, propertyRange/2), 3706 M:(dynamic functionalProperty/1, inverseFunctionalProperty/1, reflexiveProperty/1, irreflexiveProperty/1, symmetricProperty/1, asymmetricProperty/1, transitiveProperty/1, hasKey/2), 3707 M:(dynamic sameIndividual/1, differentIndividuals/1, classAssertion/2, propertyAssertion/3, negativePropertyAssertion/3), 3708 M:(dynamic annotationAssertion/3, annotation/3, ontology/1, ontologyAxiom/2, ontologyImport/2, ontologyVersionInfo/2), 3709 M:(dynamic owl/4, owl/3, owl/2, blanknode/3, outstream/1, aNN/3, annotation_r_node/4, axiom_r_node/4, owl_repository/2, trdf_setting/2), 3710 M:(dynamic ns4query/1), 3711 retractall(M:kb_atom([])), 3712 forall(trill:axiom(M:A),retractall(M:)), 3713 retractall(M:blanknode(_,_,_)), 3714 retractall(M:aNN(_,_,_)), 3715 retractall(M:annotation_r_node(_,_,_)), 3716 retractall(M:axiom_r_node(_,_,_)), 3717 retractall(M:annotation(_,_,_)), 3718 retractall(M:owl(_,_,_)), 3719 retractall(M:owl(_,_,_,_)), 3720 retractall(M:owl(_,_)), 3721 retractall(M:ontologyAxiom(_,_)), 3722 retractall(M:ontologyImport(_,_)), 3723 retractall(M:ontologyVersionInfo(_,_)), 3724 retractall(M:rdf(_,_,_)). 3725 3726set_up(M):- 3727 M:(dynamic class/1, datatype/1, objectProperty/1, dataProperty/1, annotationProperty/1), 3728 M:(dynamic namedIndividual/1, anonymousIndividual/1, subClassOf/2, equivalentClasses/1, disjointClasses/1, disjointUnion/2), 3729 M:(dynamic subPropertyOf/2, equivalentProperties/1, disjointProperties/1, inverseProperties/2, propertyDomain/2, propertyRange/2), 3730 M:(dynamic functionalProperty/1, inverseFunctionalProperty/1, reflexiveProperty/1, irreflexiveProperty/1, symmetricProperty/1, asymmetricProperty/1, transitiveProperty/1, hasKey/2), 3731 M:(dynamic sameIndividual/1, differentIndividuals/1, classAssertion/2, propertyAssertion/3, negativePropertyAssertion/3), 3732 M:(dynamic annotationAssertion/3, annotation/3, ontology/1, ontologyAxiom/2, ontologyImport/2, ontologyVersionInfo/2), 3733 M:(dynamic owl/4, owl/3, owl/2, blanknode/3, outstream/1, aNN/3, annotation_r_node/4, axiom_r_node/4, owl_repository/2, trdf_setting/2), 3734 M:(dynamic ns4query/1, addKBName/0), 3735 retractall(M:addKBName). 3736 %retractall(M:rules(_,_)), 3737 %assert(M:rules([],[])), 3738 %retractall(M:expressivity(_,_)), 3739 %assert(M:expressivity(1,[0,0,0,0,0,0])). 3740 3741set_up_kb_loading(M):- 3742 retractall(M:kb_atom(_)), 3743 init_kb_atom(M), 3744 retractall(M:addKBName), 3745 assert(M:addKBName), 3746 assert(trill_input_mode(M)). 3747 %format("Loading knowledge base...~n",[]), 3748 %statistics(walltime,[_,_]). 3749 3750init_kb_atom(M):- 3751 assert(M:kb_atom(kbatoms{annotationProperty:[],class:[],dataProperty:[],datatype:[],individual:[],objectProperty:[]})). 3752 3753init_kb_atom(M,AnnProps,Classes,DataProps,Datatypes,Inds,ObjectProps):- 3754 assert(M:kb_atom(kbatoms{annotationProperty:AnnProps,class:Classes,dataProperty:DataProps,datatype:Datatypes,individual:Inds,objectProperty:ObjectProps})). 3755 3756init_kb_atom(M,KB):- 3757 assert(M:kb_atom(kbatoms{annotationProperty:KB.annotationProperties,class:KB.classesName,dataProperty:KB.dataProperties,datatype:KB.datatypes,individual:KB.individuals,objectProperty:KB.objectProperties})). 3758 3759:- multifile sandbox:safe_primitive/1. 3760 3761sandbox:safe_primitive(utility_translation:load_owl(_)). 3762sandbox:safe_primitive(utility_translation:load_owl_from_string(_)). 3763sandbox:safe_primitive(utility_translation:expand_all_ns(_,_,_,_)). 3764sandbox:safe_primitive(utility_translation:expand_all_ns(_,_,_,_,_)). 3765%sandbox:safe_primitive(utility_translation:query_expand(_)). 3766 3767userterm_expansion(kb_prefix(A,B),[]):- 3768 get_module(M), 3769 assert(M:addKBName), 3770 trill:add_kb_prefix(M:A,B). 3771 3772userterm_expansion(owl_rdf(String),[]):- 3773 parse_rdf_from_owl_rdf_pred(String). 3774 3775userterm_expansion(end_of_file, end_of_file) :- 3776 rdf_reset_db, 3777 retractall(M:blanknode(_,_,_)), 3778 retractall(M:aNN(_,_,_)), 3779 retractall(M:annotation_r_node(_,_,_)), 3780 retractall(M:axiom_r_node(_,_,_)), 3781 retractall(M:annotation(_,_,_)), 3782 retractall(M:owl(_,_,_)), 3783 retractall(M:owl(_,_,_,_)), 3784 retractall(M:owl(_,_)), 3785 retractall(M:ontologyAxiom(_,_)), 3786 retractall(M:ontologyImport(_,_)), 3787 retractall(M:ontologyVersionInfo(_,_)), 3788 retractall(M:rdf(_,_,_)), 3789 retractall(M:trdf_setting(_,_)), 3790 get_module(M), 3791 trill_input_mode(M), 3792 dif(M,trill), 3793 dif(M,utility_translation), 3794 fix_wrongly_classified_atoms(M), 3795 retractall(M:addKBName), 3796 retractall(trill_input_mode(_)). 3797 %statistics(walltime,[_,KBLM]), 3798 %KBLS is KBLM / 1000, 3799 %format("Knowledge base loaded in ~f seconds.~n",[KBLS]). 3800 3801userterm_expansion(TRILLAxiom,[]):- 3802 get_module(M), 3803 is_axiom(TRILLAxiom), 3804 create_and_assert_axioms(M,TRILLAxiom). 3805 3806 3807/* 3808class/1,datatype/1,objectProperty/1,dataProperty/1,annotationProperty/1,namedIndividual/1,anonymousIndividual/1, 3809subClassOf/2,equivalentClasses/1,disjointClasses/1,disjointUnion/2,subPropertyOf/2,equivalentProperties/1, 3810disjointProperties/1,inverseProperties/2,propertyDomain/2,propertyRange/2,functionalProperty/1, 3811inverseFunctionalProperty/1,reflexiveProperty/1,irreflexiveProperty/1,symmetricProperty/1,asymmetricProperty/1, 3812transitiveProperty/1,hasKey/2,sameIndividual/1,differentIndividuals/1,classAssertion/2,propertyAssertion/3, 3813negativePropertyAssertion/3,annotationAssertion/3,annotation/3,ontology/1,ontologyAxiom/2,ontologyImport/2, 3814ontologyVersionInfo/2,owl/4,owl/3,owl/2,blanknode/3,outstream/1,aNN/3,annotation_r_node/4,axiom_r_node/4, 3815owl_repository/2,trdf_setting/2, 3816*/
utility_translation
This module translates OWL/RDF axioms into TRILL format and loads the knowledge base to be queried by TRILL.
The translation form OWL/RDF is based on the Thea OWL library. Thea OWL library is available under the GNU/GPL license. http://vangelisv.github.io/thea/