Chris@0: /* $Id$ Chris@0: Chris@0: Part of SWI-Prolog Chris@0: Chris@0: Author: Jan Wielemaker Chris@0: E-mail: jan@swi.psy.uva.nl Chris@0: WWW: http://www.swi-prolog.org Chris@0: Copyright (C): 1985-2002, University of Amsterdam Chris@0: Chris@0: This program is free software; you can redistribute it and/or Chris@0: modify it under the terms of the GNU General Public License Chris@0: as published by the Free Software Foundation; either version 2 Chris@0: of the License, or (at your option) any later version. Chris@0: Chris@0: This program is distributed in the hope that it will be useful, Chris@0: but WITHOUT ANY WARRANTY; without even the implied warranty of Chris@0: MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the Chris@0: GNU General Public License for more details. Chris@0: Chris@0: You should have received a copy of the GNU Lesser General Public Chris@0: License along with this library; if not, write to the Free Software Chris@0: Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Chris@0: Chris@0: As a special exception, if you link this library with other files, Chris@0: compiled with a Free Software compiler, to produce an executable, this Chris@0: library does not by itself cause the resulting executable to be covered Chris@0: by the GNU General Public License. This exception does not however Chris@0: invalidate any other reasons why the executable file might be covered by Chris@0: the GNU General Public License. Chris@0: */ Chris@0: Chris@0: :- module(owl, Chris@0: [ owl_restriction_on/2, % ?Class, ?Restriction Chris@0: owl_merged_restriction/3, % ?Class, ?Property, ?Restriction Chris@0: owl_restriction/2, % +Resource, -Restriction Chris@0: owl_description/2, % +Resource, -Description Chris@0: owl_cardinality_on_subject/3, % +Subject, +Predicate, -Card Chris@0: owl_cardinality_on_class/3, % idem BJW Chris@0: owl_satisfies/2, % +Spec, +Resource Chris@0: owl_individual_of/2, % ?Resource, +Description Chris@0: Chris@0: owl_direct_subclass_of/2, % ?Resource, ?Class Chris@0: owl_subclass_of/2, % ?Class, ?Super Chris@0: Chris@0: owl_has/3, % ?Subject, ?Predicate, ?Object Chris@0: owl_has_direct/3, % ?Subject, ?Predicate, ?Object Chris@0: owl_same_as/2, % ?X, ?Y Chris@0: Chris@0: owl_find/5 % +For, +Dom, ?Props, +Method, -Subj Chris@0: ]). Chris@0: :- use_module(library(lists)). Chris@0: :- use_module(library('semweb/rdf_db')). Chris@0: :- use_module(library('semweb/rdfs')). Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * EXPANSION * Chris@0: *******************************/ Chris@0: Chris@0: % user:goal_expansion(+NSGoal, -Goal) Chris@0: % Chris@0: % This predicate allows for writing down rdf queries in a friendly Chris@0: % name-space fashion. Chris@0: Chris@0: :- multifile Chris@0: user:goal_expansion/2. Chris@0: Chris@0: :- rdf_register_ns(swrl, Chris@0: 'http://www.w3.org/2003/11/swrl#', Chris@0: [ keep(true) Chris@0: ]). Chris@0: Chris@0: :- rdf_meta Chris@0: owl_restriction_on(r, t), Chris@0: owl_merged_restriction(r, r, t), Chris@0: owl_restriction(r, -), Chris@0: owl_description(r, -), Chris@0: owl_cardinality_on_subject(r, r, -), Chris@0: owl_cardinality_on_class(r, r, -), Chris@0: owl_satisfies(r, t), Chris@0: owl_individual_of(r, t), Chris@0: owl_direct_subclass_of(r, r), Chris@0: owl_subclass_of(r, r), Chris@0: owl_has(r, r, o), Chris@0: owl_has_direct(r, r, o), Chris@0: owl_same_as(r, r), Chris@0: owl_find(+, t, t, +, -). Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * FACTS * Chris@0: *******************************/ Chris@0: Chris@0: % owl_individual(?IndividualID, ?Type) Chris@0: % owl_property(?IndividualID, ?PropertyID, ?PropertyValue) Chris@0: % owl_same_individual(?IndividualID1, ?IndividualID2) Chris@0: % owl_different_individual(?IndividualID1, ?IndividualID2) Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * AXIOMS * Chris@0: *******************************/ Chris@0: Chris@0: % owl_class(?ClassID, ?Super) Chris@0: % owl_class_modality(?ClassID, ?Modality) Chris@0: % owl_same_class(?ClassID1, ?ClassID2) Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * RESTRICTIONS * Chris@0: *******************************/ Chris@0: Chris@0: %% owl_restriction_on(+ClassID, Chris@0: %% -Restriction:restriction(?PropertyID, ?Restriction)) is nondet. Chris@0: % Chris@0: % Enumerate the restrictions that apply to PropertyID for Class. Chris@0: % Restriction is one of Chris@0: % Chris@0: % * all_values_from(Class) Chris@0: % * some_values_from(Class) Chris@0: % * has_value(Value) Chris@0: % * cardinality(Min, Max) Chris@0: Chris@0: :- rdf_meta Chris@0: rdf_phas(r,r,o). Chris@0: Chris@0: owl_restriction_on(Class, Restriction) :- Chris@0: owl_subclass_of(Class, Super), Chris@0: ( rdfs_individual_of(Super, owl:'Restriction'), Chris@0: owl_restriction(Super, Restriction) Chris@0: ; Restriction = restriction(Property, Chris@0: all_values_from(Range)), Chris@0: rdf_phas(Property, rdfs:domain, Super), Chris@0: ( rdf_phas(Property, rdfs:range, Range) Chris@0: *-> true Chris@0: ; rdf_equal(Range, rdfs:'Resource') Chris@0: ) Chris@0: ). Chris@0: Chris@0: rdf_phas(Property, P, O) :- Chris@0: rdfs_subproperty_of(Property, Super), Chris@0: rdf_has(Super, P, O2), !, Chris@0: O = O2. Chris@0: Chris@0: %% owl_restriction(+Resource, -Prolog) is det. Chris@0: % Chris@0: % Translate Resource, an individual of owl:restriction into a Prolog term. Chris@0: % Chris@0: % @see owl_restriction_on/2 for the Prolog representation. Chris@0: Chris@0: owl_restriction(RestrictionID, restriction(Property, Restriction)) :- Chris@0: rdf_has(RestrictionID, owl:onProperty, Property), Chris@0: restriction_facet(RestrictionID, Restriction). Chris@0: Chris@0: restriction_facet(RestrictionID, R) :- Chris@0: ( rdf_has(RestrictionID, owl:allValuesFrom, Class) Chris@0: -> R = all_values_from(Class) Chris@0: ; rdf_has(RestrictionID, owl:someValuesFrom, Class) Chris@0: -> R = some_values_from(Class) Chris@0: ). Chris@0: restriction_facet(RestrictionID, has_value(Value)) :- Chris@0: rdf_has(RestrictionID, owl:hasValue, Value). Chris@0: restriction_facet(R, cardinality(Min, Max)) :- Chris@0: ( rdf_has(R, owl:cardinality, literal(Atom)) Chris@0: -> non_negative_integer(Atom, Min, R, owl:cardinality), Chris@0: Max = Min Chris@0: ; rdf_has(R, owl:minCardinality, literal(MinAtom)) Chris@0: -> non_negative_integer(MinAtom, Min, R, owl:minCardinality), Chris@0: ( rdf_has(R, owl:maxCardinality, literal(MaxAtom)) Chris@0: -> non_negative_integer(MaxAtom, Max, R, owl:maxCardinality) Chris@0: ; Max = inf Chris@0: ) Chris@0: ; rdf_has(R, owl:maxCardinality, literal(MaxAtom)) Chris@0: -> non_negative_integer(MaxAtom, Max, R, owl:maxCardinality), Chris@0: Min = 0 Chris@0: ). Chris@0: Chris@0: % non_negative_integer(+Atom, -Integer, +Subject, +Predicate) Chris@0: % Chris@0: % Deduce integer value from rdf(Subject, Predicate, literal(Atom)) Chris@0: % and if a conversion error occurs warn compatible to the rdfs_validate Chris@0: % library. Chris@0: % Chris@0: % TBD: If argument is typed we should check the type is compatible Chris@0: % to xsd:nonNegativeInteger. Chris@0: Chris@0: non_negative_integer(type(_Type, Atom), Int, S, P) :- Chris@0: nonvar(Atom), !, Chris@0: non_negative_integer(Atom, Int, S, P). Chris@0: non_negative_integer(Atom, Int, _, _) :- Chris@0: catch(atom_number(Atom, Int), _, fail), !, Chris@0: integer(Int), Chris@0: Int >= 0. Chris@0: non_negative_integer(Atom, _, S, P) :- Chris@0: rdf_equal(xsd:nonNegativeInteger, Range), Chris@0: rdf_global_id(P, Pred), Chris@0: print_message(error, Chris@0: rdf_illegal_object(S,Pred,literal(Atom),Range)), Chris@0: fail. Chris@0: Chris@0: %% owl_merged_restriction(+Class, ?Property, ?Restriction) is nondet. Chris@0: % Chris@0: % As owl_restriction_on/2, but combines multiple restrictions into Chris@0: % the least strict restriction satisfying the declared Chris@0: % restrictions. Chris@0: Chris@0: owl_merged_restriction(Class, Property, Restriction) :- Chris@0: setof(Decl, Chris@0: owl_restriction_on(Class, restriction(Property, Decl)), Chris@0: Decls), Chris@0: join_decls(Decls, Minimal), Chris@0: member(Restriction, Minimal). Chris@0: Chris@0: % input is sorted, thus the following holds: Chris@0: % Chris@0: % cardinality < has_value < values_from Chris@0: Chris@0: join_decls([], []). Chris@0: join_decls([cardinality(Min1, Max1), cardinality(Min2, Max2)|T], Set) :- !, Chris@0: Min is max(Min1, Min2), Chris@0: max_cardinality(Max1, Max2, Max), Chris@0: join_decls([cardinality(Min, Max)|T], Set). Chris@0: join_decls([has_value(Value)|T], [has_value(Value)]) :- !, Chris@0: satisfies_restrictions(T, Value). Chris@0: join_decls([values_from(AS1, C1), values_from(AS2, C2)|T], Set) :- Chris@0: merge_values_from(AS1, C1, AS2, C2, AS, C), !, Chris@0: join_decls([values_from(AS, C)|T], Set). Chris@0: join_decls([H|T0], [H|T]) :- Chris@0: join_decls(T0, T). Chris@0: Chris@0: max_cardinality(infinite, Min, Min) :- !. Chris@0: max_cardinality(Min, infinite, Min) :- !. Chris@0: max_cardinality(Min1, Min2, Min) :- Chris@0: Min is min(Min1, Min2). Chris@0: Chris@0: % satisfies_restrictions(+Restrictions, +Value) Chris@0: % Chris@0: % See whether Value satisfies all restrictions, so we can indeed Chris@0: % use it as a value. Chris@0: Chris@0: satisfies_restrictions([], _). Chris@0: satisfies_restrictions([H|T], Value) :- Chris@0: satisfies_restriction(H, Value), Chris@0: satisfies_restrictions(T, Value). Chris@0: Chris@0: satisfies_restriction(has_value(Value), Value). Chris@0: satisfies_restriction(values_from(some, _), _). Chris@0: satisfies_restriction(values_from(all, Class), Value) :- Chris@0: rdfs_individual_of(Value, Class). Chris@0: Chris@0: % merge_values_from(+AllSome2, +C1, +AllSome2, +C2, -AllSome, -C) Chris@0: % Chris@0: % Merge multiple allValuesFrom and someValuesFrom restrictions. Chris@0: % This needs some thought, but as we don't need it for the MIA Chris@0: % tool right now we'll leave it. Chris@0: Chris@0: merge_values_from(all, C1, all, C2, all, C) :- Chris@0: rdfs_subclass_of(C, C1), Chris@0: rdfs_subclass_of(C, C2). Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * CARDINALITY * Chris@0: *******************************/ Chris@0: Chris@0: %% owl_cardinality_on_subject(+Subject, +Pred, -Card:cardinality(Min, Max)) is semidet. Chris@0: % Chris@0: % Deduces the minimum and maximum cardinality for a property of a Chris@0: % resource. This predicate may fail if no information is available. Chris@0: % Chris@0: % NOTE: used to use rdf_subclass_of. Will owl_direct_subclass_of lead to Chris@0: % cycles? Chris@0: Chris@0: owl_cardinality_on_subject(Subject, Predicate, Cardinality) :- Chris@0: findall(C, cardinality_on_subject(Subject, Predicate, C), L), Chris@0: join_decls(L, [Cardinality]). Chris@0: Chris@0: cardinality_on_subject(Subject, Predicate, cardinality(Min, Max)) :- Chris@0: rdf_has(Subject, rdf:type, Class), Chris@0: owl_direct_subclass_of(Class, RestrictionID), Chris@0: rdfs_individual_of(RestrictionID, owl:'Restriction'), Chris@0: rdf_has(RestrictionID, owl:onProperty, Predicate), Chris@0: restriction_facet(RestrictionID, cardinality(Min, Max)). Chris@0: Chris@0: %% owl_cardinality_on_class(+Class, ?Predicate, -Card:cardinality(Min, Max)) is semidet. Chris@0: Chris@0: owl_cardinality_on_class(Class, Predicate, Cardinality) :- Chris@0: findall(C, cardinality_on_class(Class, Predicate, C), L), Chris@0: join_decls(L, [Cardinality]). Chris@0: Chris@0: cardinality_on_class(Class, Predicate, cardinality(Min, Max)) :- Chris@0: owl_direct_subclass_of(Class, RestrictionID), Chris@0: rdfs_individual_of(RestrictionID, owl:'Restriction'), Chris@0: rdf_has(RestrictionID, owl:onProperty, Predicate), Chris@0: restriction_facet(RestrictionID, cardinality(Min, Max)). Chris@0: Chris@0: %% owl_satisfies_restriction(?Resource, +Restriction) Chris@0: % Chris@0: % True if Restriction satisfies the restriction imposed by Restriction. Chris@0: % The current implementation makes the following assumptions: Chris@0: % Chris@0: % * Only one of owl:hasValue, owl:allValuesFrom or owl:someValuesFrom Chris@0: % is present. Chris@0: Chris@0: owl_satisfies_restriction(Resource, Restriction) :- Chris@0: rdf_has(Restriction, owl:onProperty, Property), Chris@0: ( rdf_has(Restriction, owl:hasValue, Value) Chris@0: -> owl_has(Resource, Property, Value) Chris@0: ; rdf_has(Restriction, owl:allValuesFrom, Class) Chris@0: -> setof(V, owl_has(Resource, Property, V), Vs), Chris@0: all_individual_of(Vs, Class) Chris@0: ; rdf_has(Restriction, owl:someValuesFrom, Class) Chris@0: -> owl_has(Resource, Property, Value), Chris@0: owl_individual_of(Value, Class) Chris@0: ; rdf_subject(Resource) Chris@0: ), Chris@0: owl_satisfies_cardinality(Resource, Restriction). Chris@0: Chris@0: all_individual_of([], _). Chris@0: all_individual_of([H|T], Class) :- Chris@0: owl_individual_of(H, Class), !, Chris@0: all_individual_of(T, Class). Chris@0: Chris@0: % owl_satisfies_cardinality(?Resource[, +Property], +Restriction) Chris@0: % Chris@0: % True if Resource satisfies the cardinality restrictions on Chris@0: % Property imposed by Restriction. Chris@0: Chris@0: owl_satisfies_cardinality(Resource, Restriction) :- Chris@0: rdf_has(Restriction, owl:onProperty, Property), Chris@0: owl_satisfies_cardinality(Resource, Property, Restriction). Chris@0: Chris@0: owl_satisfies_cardinality(Resource, Property, Restriction) :- Chris@0: rdf_has(Restriction, owl:cardinality, literal(Atom)), !, Chris@0: non_negative_int(Atom, Card), Chris@0: findall(V, rdf_has(Resource, Property, V), Vs0), Chris@0: sort(Vs0, Vs), % remove duplicates Chris@0: length(Vs, Card). Chris@0: owl_satisfies_cardinality(Resource, Property, Restriction) :- Chris@0: rdf_has(Restriction, owl:minCardinality, literal(MinAtom)), Chris@0: non_negative_int(MinAtom, Min), !, Chris@0: findall(V, owl_has(Resource, Property, V), Vs0), Chris@0: sort(Vs0, Vs), % remove duplicates Chris@0: length(Vs, Count), Chris@0: Count >= Min, Chris@0: ( rdf_has(Restriction, owl:maxCardinality, literal(MaxAtom)), Chris@0: atom_number(MaxAtom, Max) Chris@0: -> Count =< Max Chris@0: ; true Chris@0: ). Chris@0: owl_satisfies_cardinality(Resource, Property, Restriction) :- Chris@0: rdf_has(Restriction, owl:maxCardinality, literal(MaxAtom)), Chris@0: non_negative_int(MaxAtom, Max), !, Chris@0: findall(V, owl_has(Resource, Property, V), Vs0), Chris@0: sort(Vs0, Vs), % remove duplicates Chris@0: length(Vs, Count), Chris@0: Count =< Max. Chris@0: owl_satisfies_cardinality(Resource, _, _) :- Chris@0: rdf_subject(Resource). Chris@0: Chris@0: non_negative_int(type(Type, Atom), Number) :- Chris@0: rdf_equal(xsd:nonNegativeInteger, Type), Chris@0: catch(atom_number(Atom, Number), _, fail). Chris@0: non_negative_int(Atom, Number) :- Chris@0: atom(Atom), Chris@0: catch(atom_number(Atom, Number), _, fail). Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * DESCRIPTION * Chris@0: *******************************/ Chris@0: Chris@0: %% owl_description(+DescriptionID, -Prolog) is det. Chris@0: % Chris@0: % Convert an owl description into a Prolog representation. This Chris@0: % representation is: Chris@0: % Chris@0: % * class(Class) Chris@0: % * restriction(Property, Restriction) Chris@0: % * union_of(ListOfDescriptions) Chris@0: % * intersection_of(ListOfDescriptions) Chris@0: % * complement_of(Description) Chris@0: % * one_of(Individuals) Chris@0: % * thing Chris@0: % * nothing Chris@0: % Chris@0: % where Restriction is defined by owl_restriction_on/2. Chris@0: % For example, the union-of can be the result of Chris@0: % Chris@0: % == Chris@0: % Chris@0: % Chris@0: % Chris@0: % Chris@0: % Chris@0: % Chris@0: % == Chris@0: Chris@0: owl_description(ID, Restriction) :- Chris@0: ( rdf_equal(owl:'Thing', ID) Chris@0: -> Restriction = thing Chris@0: ; rdf_equal(owl:'Nothing', ID) Chris@0: -> Restriction = nothing Chris@0: ; rdf_has(ID, rdf:type, owl:'Restriction') Chris@0: -> owl_restriction(ID, Restriction) Chris@0: ; rdf_has(ID, rdf:type, owl:'Class') Chris@0: -> ( ( rdf_has(ID, owl:unionOf, Set) Chris@0: -> Restriction = union_of(SubDescriptions) Chris@0: ; rdf_has(ID, owl:intersectionOf, Set) Chris@0: -> Restriction = intersection_of(SubDescriptions) Chris@0: ) Chris@0: -> rdfs_list_to_prolog_list(Set, Members), Chris@0: maplist(owl_description, Members, SubDescriptions) Chris@0: ; rdf_has(ID, owl:complementOf, Arg) Chris@0: -> Restriction = complement_of(SubDescription), Chris@0: owl_description(Arg, SubDescription) Chris@0: ; rdf_has(ID, owl:oneOf, Arg) Chris@0: -> Restriction = one_of(Individuals), Chris@0: rdfs_list_to_prolog_list(Arg, Individuals) Chris@0: ; Restriction = class(ID) Chris@0: ) Chris@0: ). Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * OWL_SATISFIES * Chris@0: *******************************/ Chris@0: Chris@0: %% owl_satisfies(+Specification, ?Resource) is nondet. Chris@0: % Chris@0: % Test whether Resource satisfies Specification. All resources are Chris@0: % considered to belong to rdfs:Resource, which is not really Chris@0: % enforced. Domain is one of Chris@0: % Chris@0: % | rdfs:Resource | Allow for any resource | Chris@0: % | class(Class) | Allow for a subclass of Class| Chris@0: % | union_of(Domains) | | Chris@0: % | intersection_of(Domains) | | Chris@0: % | complement_of(Domain) | | Chris@0: % | one_of(Resources) | One of these values | Chris@0: % | all_values_from(Class) | Individual of this class | Chris@0: % | some_values_from(Class) | Not used | Chris@0: % | has_value(Value) | Must have this value | Chris@0: % Chris@0: % Resource can be a term individual_of(Class), in which case this Chris@0: % predicate succeeds if any individual of Class is accepted by Chris@0: % Domain. Chris@0: Chris@0: % Short-cut Chris@0: owl_satisfies(Domain, Resource) :- Chris@0: rdf_equal(rdfs:'Resource', Domain), !, Chris@0: ( atom(Resource) Chris@0: -> true Chris@0: ; var(Resource) Chris@0: -> rdf_subject(Resource) Chris@0: ; Resource = individual_of(_) Chris@0: ). Chris@0: % Descriptions Chris@0: owl_satisfies(class(Domain), Resource) :- !, Chris@0: ( rdf_equal(Domain, rdfs:'Resource') Chris@0: -> true Chris@0: ; Resource = individual_of(Class), Chris@0: atom(Class) Chris@0: -> fail Chris@0: ; owl_subclass_of(Resource, Domain) Chris@0: ). Chris@0: owl_satisfies(union_of(Domains), Resource) :- !, Chris@0: member(Domain, Domains), Chris@0: owl_satisfies(Domain, Resource). Chris@0: owl_satisfies(intersection_of(Domains), Resource) :- !, Chris@0: in_all_domains(Domains, Resource). Chris@0: owl_satisfies(complement_of(Domain), Resource) :- !, Chris@0: ( atom(Resource) Chris@0: -> true Chris@0: ; var(Resource) Chris@0: -> rdf_subject(Resource) Chris@0: ; fail % individual_of(Class) Chris@0: ), Chris@0: \+ owl_satisfies(Domain, Resource). Chris@0: owl_satisfies(one_of(List), Resource) :- !, Chris@0: member(Resource, List). Chris@0: % Restrictions Chris@0: owl_satisfies(all_values_from(Domain), Resource) :- !, Chris@0: ( Resource = individual_of(Class), Chris@0: atom(Class) Chris@0: -> owl_subclass_of(Class, Domain) Chris@0: ; owl_individual_of(Resource, Domain) Chris@0: ). Chris@0: owl_satisfies(some_values_from(_Domain), _Resource) :- !. Chris@0: owl_satisfies(has_value(Value), Resource) :- Chris@0: rdf_equal(Value, Resource). % TBD: equality Chris@0: Chris@0: Chris@0: in_all_domains([], _). Chris@0: in_all_domains([H|T], Resource) :- Chris@0: owl_satisfies(H, Resource), Chris@0: in_all_domains(T, Resource). Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * INDIVIDUAL OF * Chris@0: *******************************/ Chris@0: Chris@0: %% owl_individual_of(?Resource, +Description) is nondet. Chris@0: % Chris@0: % Test or generate the resources that satisfy Description Chris@0: % according the the OWL-Description entailment rules. Chris@0: Chris@0: owl_individual_of(Resource, Thing) :- Chris@0: rdf_equal(Thing, owl:'Thing'), !, Chris@0: ( atom(Resource) Chris@0: -> true Chris@0: ; rdf_subject(Resource) Chris@0: ). Chris@0: owl_individual_of(_Resource, Nothing) :- Chris@0: rdf_equal(Nothing, owl:'Nothing'), !, Chris@0: fail. Chris@0: owl_individual_of(Resource, Description) :- % RDFS Chris@0: rdfs_individual_of(Resource, Description). Chris@0: /*owl_individual_of(Resource, Class) :- Chris@0: nonvar(Resource), Chris@0: setof(C, rdf_has(Resource, rdf:type, C), Cs), !, Chris@0: member(C, Cs), Chris@0: owl_subclass_of(C, Class). Chris@0: */ Chris@0: owl_individual_of(Resource, Class) :- Chris@0: nonvar(Resource), Chris@0: rdf_has(Resource, rdf:type, C), Chris@0: owl_subclass_of(C, Class). Chris@0: Chris@0: owl_individual_of(Resource, Class) :- Chris@0: rdfs_individual_of(Class, owl:'Class'), Chris@0: ( rdf_has(Class, owl:equivalentClass, EQ) Chris@0: -> owl_individual_of(Resource, EQ) Chris@0: ; rdfs_individual_of(Class, owl:'Restriction') Chris@0: -> owl_satisfies_restriction(Resource, Class) Chris@0: ; owl_individual_of_description(Resource, Class, HasDescription), Chris@0: findall(SC, rdf_has(Class, rdfs:subClassOf, SC), SuperClasses), Chris@0: ( HasDescription == false Chris@0: -> SuperClasses \== [] Chris@0: ; true Chris@0: ), Chris@0: owl_individual_of_all(SuperClasses, Resource) Chris@0: ). Chris@0: owl_individual_of(Resource, Description) :- % RDFS Chris@0: owl_individual_from_range(Resource, Description). Chris@0: Chris@0: Chris@0: %% owl_individual_of_description(?Resource, +Description, -HasDescription) is nondet. Chris@0: % Chris@0: % @tbd Can a description have multiple of these facets? Chris@0: Chris@0: owl_individual_of_description(Resource, Description, true) :- Chris@0: rdf_has(Description, owl:unionOf, Set), !, Chris@0: rdfs_member(Sub, Set), Chris@0: owl_individual_of(Resource, Sub). Chris@0: owl_individual_of_description(Resource, Description, true) :- Chris@0: rdf_has(Description, owl:intersectionOf, Set), !, Chris@0: intersection_of(Set, Resource). Chris@0: owl_individual_of_description(Resource, Description, true) :- Chris@0: rdf_has(Description, owl:complementOf, Arg), !, Chris@0: rdf_subject(Resource), Chris@0: \+ owl_individual_of(Resource, Arg). Chris@0: owl_individual_of_description(Resource, Description, true) :- Chris@0: rdf_has(Description, owl:oneOf, Arg), !, Chris@0: rdfs_member(Resource, Arg). Chris@0: owl_individual_of_description(_, _, false). Chris@0: Chris@0: Chris@0: owl_individual_of_all([], _). Chris@0: owl_individual_of_all([C|T], Resource) :- Chris@0: owl_individual_of(Resource, C), Chris@0: owl_individual_of_all(T, Resource). Chris@0: Chris@0: Chris@0: owl_individual_from_range(Resource, Class) :- Chris@0: nonvar(Resource), !, Chris@0: rdf_has(_, P, Resource), Chris@0: rdf_has(P, rdfs:range, Class), !. Chris@0: owl_individual_from_range(Resource, Class) :- Chris@0: rdf_has(P, rdfs:range, Class), Chris@0: rdf_has(_, P, Resource). % owl_has? Chris@0: Chris@0: intersection_of(List, Resource) :- Chris@0: rdf_has(List, rdf:first, First), Chris@0: owl_individual_of(Resource, First), Chris@0: ( rdf_has(List, rdf:rest, Rest) Chris@0: -> intersection_of(Rest, Resource) Chris@0: ; true Chris@0: ). Chris@0: intersection_of(Nil, _) :- Chris@0: rdf_equal(rdf:nil, Nil). Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * OWL PROPERTIES * Chris@0: *******************************/ Chris@0: Chris@0: %% owl_has(?Subject, ?Predicate, ?Object) Chris@0: % Chris@0: % True if this relation is specified or can be deduced using OWL Chris@0: % inference rules. It adds transitivity to owl_has_direct/3. Chris@0: Chris@0: owl_has(S, P, O) :- Chris@0: ( var(P) Chris@0: -> rdfs_individual_of(P, rdf:'Property') Chris@0: ; true Chris@0: ), Chris@0: rdf_reachable(SP, rdfs:subPropertyOf, P), Chris@0: owl_has_transitive(S, SP, O). Chris@0: Chris@0: Chris@0: %% owl_has_transitive(?Subject, ?Predicate, ?Object) Chris@0: % Chris@0: % If Predicate is transitive, do a transitive closure on the Chris@0: % relation. Chris@0: Chris@0: owl_has_transitive(S, P, O) :- Chris@0: rdfs_individual_of(P, owl:'TransitiveProperty'), !, Chris@0: owl_has_transitive(S, P, O, [P]). Chris@0: owl_has_transitive(S, P, O) :- Chris@0: owl_has_equivalent(S, P, O). Chris@0: Chris@0: owl_has_transitive(S, P, O, Visited) :- Chris@0: owl_has_equivalent(S, P, O1), Chris@0: O1 \= literal(_), Chris@0: \+ memberchk(O1, Visited), Chris@0: ( O = O1 Chris@0: ; owl_has_transitive(O1, P, O, [O1|Visited]) Chris@0: ). Chris@0: Chris@0: % owl_has_equivalent(?Subject, ?Predicate, ?Object) Chris@0: % Chris@0: % Adds owl:sameAs on Subject and Object to owl_has_direct/3 Chris@0: Chris@0: owl_has_equivalent(S, P, O) :- Chris@0: nonvar(S), !, Chris@0: owl_same_as(S, S1), Chris@0: owl_has_direct(S1, P, O0), Chris@0: owl_same_as(O0, O). Chris@0: owl_has_equivalent(S, P, O) :- Chris@0: nonvar(O), !, Chris@0: owl_same_as(O1, O), Chris@0: owl_has_direct(S0, P, O1), Chris@0: owl_same_as(S0, S). Chris@0: owl_has_equivalent(S, P, O) :- Chris@0: owl_has_direct(S0, P, O0), Chris@0: owl_same_as(S0, S), Chris@0: owl_same_as(O0, O). Chris@0: Chris@0: Chris@0: %% owl_same_as(?X, ?Y) is nondet. Chris@0: % Chris@0: % True if X and Y are identical or connected by the owl:sameAs Chris@0: % relation. Considers owl:sameAs transitive and symetric. Chris@0: Chris@0: owl_same_as(literal(X), literal(X)) :- !. Chris@0: owl_same_as(X, Y) :- Chris@0: nonvar(X), !, Chris@0: owl_same_as(X, Y, [X]). Chris@0: owl_same_as(X, Y) :- Chris@0: owl_same_as(Y, X, [X]). Chris@0: Chris@0: owl_same_as(X, X, _). Chris@0: owl_same_as(X, Y, Visited) :- Chris@0: ( rdf_has(X, owl:sameAs, X1) Chris@0: ; rdf_has(X1, owl:sameAs, X) Chris@0: ), Chris@0: X1 \= literal(_), Chris@0: \+ memberchk(X1, Visited), Chris@0: owl_same_as(X1, Y, [X1|Visited]). Chris@0: Chris@0: Chris@0: %% owl_has_direct(?Subject, ?Predicate, ?Object) Chris@0: % Chris@0: % Deals with `One-step' OWL inferencing: inverse properties, Chris@0: % symmetric properties and being subtype of a restriction with an Chris@0: % owl:hasValue statement on this property. Chris@0: % Chris@0: % @bug owl_has_direct/3 also uses SWRL rules. This should be Chris@0: % moved elsewhere. Chris@0: Chris@0: owl_has_direct(S, P, O) :- Chris@0: rdf(S, P, O). Chris@0: owl_has_direct(S, P, O) :- Chris@0: ( rdf_has(P, owl:inverseOf, P2) Chris@0: -> true Chris@0: ; rdf_has(P2, owl:inverseOf, P) Chris@0: ), Chris@0: rdf_has(O, P2, S). % TBD: must call owl_has_direct/3 Chris@0: owl_has_direct(S, P, O) :- Chris@0: rdfs_individual_of(P, owl:'SymmetricProperty'), Chris@0: rdf(O, P, S). Chris@0: owl_has_direct(S, P, O) :- Chris@0: owl_use_has_value(S, P, O). Chris@0: Chris@0: Chris@0: %---------------------------------------------------------- Chris@0: % added by BJW for use of OWL with SWRL rules, highly experimental Chris@0: % see http://www.daml.org/rules/proposal/rules-all.html for SWRL. Chris@0: % It implements simple Prolog-like inferencing were order of antecedents Chris@0: % may matter and some assumptions about instantiation of variables are Chris@0: % made (see comments below). Chris@0: % Currently is doesnot cater for arbitrary OWL descriptions mixed with Chris@0: % SWRL. Chris@0: Chris@0: owl_has_direct(S, P, O) :- Chris@0: owl_use_rule(S, P, O). Chris@0: Chris@0: owl_use_rule(S, P, O):- Chris@0: rdf(Rule, rdf:type, swrl:'Impl'), % pick a rule Chris@0: rdf(Rule, swrl:head, HeadList), Chris@0: rdfs_member(IPA, HeadList), % can we use the rule? Chris@0: rdf(IPA, rdf:type, swrl:'IndividualPropertyAtom'), Chris@0: rdf(IPA, swrl:propertyPredicate, P), % IndividualPropertyAtom Chris@0: rdf(Rule, swrl:body, BodyList), % yes Chris@0: rdfs_list_to_prolog_list(BodyList, BL), Chris@0: rdf_has(IPA, swrl:argument1, A1), Chris@0: rdf_has(IPA, swrl:argument2, A2), Chris@0: ( nonvar(S) Chris@0: -> ( nonvar(O) -> SL = [A1/S, A2/O] Chris@0: ; SL= [A1/S] Chris@0: ) Chris@0: ; nonvar(O) Chris@0: -> SL = [A2/O] Chris@0: ; SL = [] Chris@0: ), Chris@0: owl_evaluate_body(BL, SL, Subst), Chris@0: ignore(member(A1/S, Subst)), % make sure S and O are instantiated Chris@0: ignore(member(A2/O, Subst)). % could probably be done more elegantly Chris@0: Chris@0: owl_evaluate_body([], Subst, Subst). Chris@0: owl_evaluate_body([IPA| Rest], SL, Subst):- Chris@0: rdf(IPA, rdf:type, swrl:'IndividualPropertyAtom'), Chris@0: rdf(IPA, swrl:propertyPredicate, P), % IPA = IndividualPropertyAtom Chris@0: rdf_has(IPA, swrl:argument1, A1), % maybe rdf instead of rdf_has? BJW Chris@0: rdf_has(IPA, swrl:argument2, A2), Chris@0: owl_has_swrl(A1, P, A2, SL, Subst1), Chris@0: owl_evaluate_body(Rest, Subst1, Subst). Chris@0: owl_evaluate_body([DF| Rest], SL, Subst):- Chris@0: rdf(DF, rdf:type, swrl:'DifferentIndividualsAtom'), Chris@0: rdf_has(DF, swrl:argument1, A1), Chris@0: instantiated(A1, S, SL), % assume both arguments are instantiated Chris@0: rdf_has(DF, swrl:argument2, A2), Chris@0: instantiated(A2, O, SL), % this assumption is to be discussed Chris@0: \+ owl_same_as(S,O), Chris@0: owl_evaluate_body(Rest, SL, Subst). Chris@0: owl_evaluate_body([SF| Rest], SL, Subst):- Chris@0: rdf(SF, rdf:type, swrl:'SameIndividualAtom'), Chris@0: rdf_has(SF, swrl:argument1, A1), Chris@0: instantiated(A1, S, SL), % assume both arguments are instantiated Chris@0: rdf_has(SF, swrl:argument2, A2), Chris@0: instantiated(A2, O, SL), % this assumption is to be discussed Chris@0: owl_same_as(S,O), % Chris@0: owl_evaluate_body(Rest, SL, Subst). Chris@0: owl_evaluate_body([CA| Rest], SL, Subst):- Chris@0: rdf(CA, rdf:type, swrl:'ClassAtom'), Chris@0: rdf_has(CA, swrl:argument1, A1), Chris@0: ( instantiated(A1, S, SL) -> SL1=SL Chris@0: ; SL1 = [A1/S|SL]), Chris@0: rdf(CA, swrl:classPredicate, Class), Chris@0: owl_individual_of(S, Class), Chris@0: owl_evaluate_body(Rest, SL1, Subst). Chris@0: Chris@0: owl_has_swrl(A1, P, A2, Subst, Subst):- % this can probably be done better BJW Chris@0: instantiated(A1, S, Subst), Chris@0: instantiated(A2, O, Subst),!, % dont backtrack here, proof complete Chris@0: owl_has(S, P, O). Chris@0: owl_has_swrl(A1, P, A2, Subst, [A1/S|Subst]):- Chris@0: is_swrl_variable(A1), Chris@0: instantiated(A2, O, Subst), Chris@0: owl_has(S, P, O). Chris@0: owl_has_swrl(A1, P, A2, Subst, [A2/O| Subst] ):- Chris@0: instantiated(A1, S, Subst), Chris@0: is_swrl_variable(A2), Chris@0: owl_has(S, P, O). Chris@0: owl_has_swrl(A1, P, A2, Subst, [A1/S, A2/O| Subst]):- % too general? Chris@0: \+ instantiated(A1, S, Subst), Chris@0: \+ instantiated(A2, O, Subst), Chris@0: owl_has(S, P, O). Chris@0: Chris@0: is_swrl_variable(V):- Chris@0: rdf_has(V, rdf:type, swrl:'Variable'). Chris@0: Chris@0: instantiated(A, A, _Subst):- Chris@0: \+ rdf_has(A, rdf:type, swrl:'Variable'). Chris@0: instantiated(A, S, Subst):- Chris@0: rdf_has(A, rdf:type, swrl:'Variable'), Chris@0: member(A/S, Subst). Chris@0: Chris@0: %end additions BJW Chris@0: %---------------------------------------------------------- Chris@0: owl_use_has_value(S, P, O) :- Chris@0: nonvar(P), !, Chris@0: rdf_has(Super, owl:onProperty, P), Chris@0: rdf_has(Super, owl:hasValue, O), Chris@0: owl_direct_subclass_of(Type, Super), Chris@0: rdf_has(S, rdf:type, Type). Chris@0: owl_use_has_value(S, P, O) :- Chris@0: rdf_has(S, rdf:type, Type), Chris@0: owl_direct_subclass_of(Type, Super), Chris@0: rdfs_individual_of(Super, owl:'Restriction'), Chris@0: rdf_has(Super, owl:onProperty, P), Chris@0: rdf_has(Super, owl:hasValue, O). Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * OWL CLASS HIERARCHY * Chris@0: *******************************/ Chris@0: Chris@0: /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - Chris@0: TBD: It is here that we must use a DL classifier! Chris@0: - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */ Chris@0: Chris@0: %% owl_direct_subclass_of(-SubClass, +Class) is nondet. Chris@0: %% owl_direct_subclass_of(+SubClass, -Class) is nondet. Chris@0: % Chris@0: % Returns both the RDFS subclasses and subclass relations implied by Chris@0: % owl:intersectionOf and owl:unionOf descriptions. Chris@0: % Chris@0: % @tbd Should use full DL reasoning Chris@0: Chris@0: owl_direct_subclass_of(Class, R) :- Chris@0: rdf_has(Class, rdfs:subClassOf, R). Chris@0: owl_direct_subclass_of(Class, R) :- % added BJW (hack for symetry) Chris@0: rdf_has(R, owl:equivalentClass, Class). Chris@0: owl_direct_subclass_of(Class, R) :- Chris@0: ( nonvar(R) Chris@0: -> ( rdf_has(R, owl:unionOf, Union), Chris@0: rdfs_member(Class, Union) Chris@0: ; rdf_has(List, rdf:first, R), Chris@0: list_head(List, Head), Chris@0: rdf_has(Class, owl:intersectionOf, Head) Chris@0: ) Chris@0: ; nonvar(Class) Chris@0: -> ( rdf_has(Class, owl:intersectionOf, List), Chris@0: rdfs_member(R, List) Chris@0: ; rdf_has(List, rdf:first, Class), Chris@0: list_head(List, Head), Chris@0: rdf_has(R, owl:unionOf, Head) Chris@0: ) Chris@0: ; throw(error(instantiation_error, _)) Chris@0: ). Chris@0: Chris@0: list_head(List, Head) :- Chris@0: ( rdf_has(H, rdf:rest, List) Chris@0: -> list_head(H, Head) Chris@0: ; Head = List Chris@0: ). Chris@0: Chris@0: Chris@0: %% owl_subclass_of(+Sub, -Super) is nondet. Chris@0: %% owl_subclass_of(-Sub, +Super) is nondet. Chris@0: % Chris@0: % Transitive version of owl_direct_subclass_of/2. Chris@0: Chris@0: owl_subclass_of(Class, Super) :- Chris@0: rdf_equal(rdfs:'Resource', Resource), Chris@0: Super == Resource, !, Chris@0: ( nonvar(Class) Chris@0: -> true Chris@0: ; rdfs_individual_of(Class, owl:'Class') Chris@0: ). Chris@0: owl_subclass_of(Class, Super) :- Chris@0: nonvar(Class), nonvar(Super), !, Chris@0: owl_test_subclass(Class, Super). Chris@0: owl_subclass_of(Class, Super) :- Chris@0: nonvar(Class), !, Chris@0: owl_gen_supers(Class, [], Super). Chris@0: owl_subclass_of(Class, Super) :- Chris@0: nonvar(Super), !, Chris@0: owl_gen_subs(Super, [], Class). Chris@0: owl_subclass_of(_, _) :- Chris@0: throw(error(instantiation_error, _)). Chris@0: Chris@0: owl_gen_supers(Class, _, Class). Chris@0: owl_gen_supers(Class, Visited, Super) :- Chris@0: ( owl_direct_subclass_of(Class, Super0) Chris@0: *-> true Chris@0: ; rdf_equal(Super0, rdfs:'Resource') Chris@0: ), Chris@0: \+ memberchk(Super0, Visited), Chris@0: owl_gen_supers(Super0, [Super0|Visited], Super). Chris@0: Chris@0: owl_gen_subs(Class, _, Class). Chris@0: owl_gen_subs(Class, Visited, Sub) :- Chris@0: owl_direct_subclass_of(Sub0, Class), Chris@0: \+ memberchk(Sub0, Class), Chris@0: owl_gen_subs(Sub0, [Sub0|Visited], Sub). Chris@0: Chris@0: Chris@0: %% owl_test_subclass(+Class, +Super) is semidet. Chris@0: % Chris@0: % Cached check for OWL subclass relation. Chris@0: Chris@0: :- dynamic Chris@0: subclass_cache/3, % +C1, +C2, -Boolean Chris@0: subclass_generation/1. % RDF generation of last compute Chris@0: Chris@0: owl_test_subclass(Class, Super) :- Chris@0: ( rdf_generation(G), Chris@0: subclass_generation(G2), Chris@0: G \== G2 Chris@0: -> retractall(subclass_cache(_,_,_)) Chris@0: ; true Chris@0: ), Chris@0: ( subclass_cache(Class, Super, Bool) Chris@0: -> Bool = true Chris@0: ; ( owl_gen_supers(Class, [], Super) Chris@0: -> assert(subclass_cache(Class, Super, true)) Chris@0: ; assert(subclass_cache(Class, Super, false)), Chris@0: fail Chris@0: ) Chris@0: ). Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * SEARCH IN HIERARCHY * Chris@0: *******************************/ Chris@0: Chris@0: %% owl_find(+String, +Domain, ?Properties, +Method, -Subject) is nondet. Chris@0: % Chris@0: % Search all classes below Domain for a literal property with Chris@0: % that matches String. Method is one of Chris@0: % Chris@0: % * substring Chris@0: % * word Chris@0: % * prefix Chris@0: % * exact Chris@0: % Chris@0: % domain is defined by owl_satisfies/2 from owl.pl Chris@0: % Chris@0: % Note that the rdfs:label field is handled by rdfs_label/2, Chris@0: % making the URI-ref fragment name the last resort to determine Chris@0: % the label. Chris@0: % Chris@0: % @tbd Use the RDF literal primitives Chris@0: Chris@0: owl_find(String, Domain, Fields, Method, Subject) :- Chris@0: var(Fields), !, Chris@0: For =.. [Method,String], Chris@0: rdf_has(Subject, Field, literal(For, _)), Chris@0: owl_satisfies(Domain, Subject), Chris@0: Fields = [Field]. % report where we found it. Chris@0: owl_find(String, Domain, Fields, Method, Subject) :- Chris@0: globalise_list(Fields, GlobalFields), Chris@0: For =.. [Method,String], Chris@0: member(Field, GlobalFields), Chris@0: ( Field == resource Chris@0: -> rdf_subject(Subject), Chris@0: rdf_match_label(Method, String, Subject) Chris@0: ; rdf_has(Subject, Field, literal(For, _)) Chris@0: ), Chris@0: owl_satisfies(Domain, Subject). Chris@0: Chris@0: globalise_list([], []) :- !. Chris@0: globalise_list([H0|T0], [H|T]) :- !, Chris@0: globalise_list(H0, H), Chris@0: globalise_list(T0, T). Chris@0: globalise_list(X, G) :- Chris@0: rdf_global_id(X, G).