1% This file is part of the Attempto Parsing Engine (APE).
    2% Copyright 2008-2010, Kaarel Kaljurand <kaljurand@gmail.com>.
    3%
    4% The Attempto Parsing Engine (APE) is free software: you can redistribute it and/or modify it
    5% under the terms of the GNU Lesser General Public License as published by the Free Software
    6% Foundation, either version 3 of the License, or (at your option) any later version.
    7%
    8% The Attempto Parsing Engine (APE) is distributed in the hope that it will be useful, but WITHOUT
    9% ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
   10% PURPOSE. See the GNU Lesser General Public License for more details.
   11%
   12% You should have received a copy of the GNU Lesser General Public License along with the Attempto
   13% Parsing Engine (APE). If not, see http://www.gnu.org/licenses/.
   14
   15
   16:- module(drs_to_owlswrl, [
   17		drs_to_owlswrl/2,
   18		drs_to_owlswrl/4
   19	]).   20
   21:- use_module(drs_to_owlswrl_core, [
   22		condlist_to_dlquery/2,
   23		condition_oneof/3,
   24		condlist_axiomlist_with_cheat/3
   25	]).   26
   27:- use_module('../drs_to_drslist', [
   28		drs_to_drslist/2
   29	]).   30
   31:- use_module('../drs_to_sdrs', [
   32		drs_to_sdrs/2
   33	]).   34
   35:- use_module('../../logger/error_logger', [
   36		add_error_message/4,
   37		clear_messages/1
   38	]).   39
   40:- use_module(drs_to_owldrs, [
   41		drs_to_owldrs/2
   42	]).   43
   44:- use_module(transform_anonymous, [
   45		transform_anonymous/2
   46	]).

Attempto DRS to OWL 2/SWRL translator

Translate an Attempto DRS into Web Ontology Language (OWL 2), or if this fails then to Semantic Web Rule Language (SWRL).

If the translation fails then we search for errors by traversing the respective structure (e.g. implication) again. Note that the error capture is not completely implemented. Sometimes the translation simply fails and no explanatory messages are asserted.

author
- Kaarel Kaljurand
version
- 2010-11-14
license
- LGPLv3

TODO:

- general:
        - put "tricks" into a separate module
        - low priority: add a trick: if a DRS maps to a SWRL rule which uses sameAs/differentFrom,
        but replacing these with normal object properties would make the rule expressible
        directly in OWL (probably SubPropertyOf with property composition),
        then replace these with ace:equal/ace:differ-from (with equivalent
        definitions) and express the rule in OWL syntax.

- allow:
        - URGENT: John likes at least 3 cars that Mary likes. (wrong translation)
        - URGENT: Which member of Attempto is a productive-developer? (currently fails)
        - URGENT: support: What are the countries that contain Paris?
        - Every man is a human and sees the human.
        - John's age is not 21.
        - John's age is 21 or is 22.
        - Every man owns something that is "abc". (because we do allow: Every man owns "abc".)
        - For everything X for every thing Y if X likes Y then X does not hate Y.
        - Every dog hates every cat. (MAYBE)
        - Mary eats some grass. (because we do allow: Everybody that eats some meat is a carnivore.)
        - Every lady's pets are nothing but cats. (instead to/in addition to: Every lady's pet is nothing but cats.)
        - Every lady is somebody whose pets are more than 3 cats. (instead/in addition to: Every lady is somebody whose pet is more than 3 cats.)
        - John likes more than 3 women that own a car.
        - Every man is himself. (currently generates SWRL, but we could generate nothing in this case)

- check:
        - if the syntax is according to the spec: DataProperty, DataValue, DataType
        - Are the following equivalent, if so then handle all of them (currently some are rejected):
        -- t(166, 'No city overlaps-with a city that is not the city.').
        -- t(167, 'Every city overlaps-with itself or does not overlap-with a city.').
        -- t(168, 'If a city overlaps-with something X then X is the city or X is not a city.').

- better error messages for:
        - No card is valid.
        - Every man does not have to cook a chicken.
        - Every singular is every singular. (from the log)
        - top-level negation
        - top-level disjunction

- RDF/XML (deprecated):
        - There is something X. If X likes Mary then John sees Bill. (fails to be translated to RDF/XML)
        - What borders itself? (otherwise OK, but fails to be translated into RDF/XML)

- improve:
        - implement namespaces support, i.e. each name should actually be a term ':'(NS, Name)
        - better support for anonymous individuals (don't numbervar the DRS, this would make things easier)

- seems to be fixed:
        - John owns a car. John is a man. What is it?

*/

  119%:- debug(d).
  120%:- debug(owldrs).
  121%:- debug(sentence).
  122
  123
  124% Operators used in the DRS.
  125:- op(400, fx, -).  126:- op(500, xfx, =>).  127:- op(500, xfx, v).
 drs_to_owlswrl(+Drs:term, -Owl:term) is semidet
 drs_to_owlswrl(+Drs:term, +IRI:atom, -Owl:term) is semidet
 drs_to_owlswrl(+Drs:term, +IRI:atom, +Comment:atom, -Owl:term) is semidet
Converts an Attempto DRS into OWL 2/SWRL. In the beginning, the DRS is modified by drs_to_owldrs/2 in order to make the processing more straight-forward.
Arguments:
Drs- is an Attempto DRS
IRI- is a IRI relative to which all class names are to be interpreted
Comment- is a comment to be inserted into the resulting ontology (currently ignored)
Owl- is an OWL ontology in the form 'Ontology'(IRI, Axioms) where Axioms is a list of axioms that correspond to the DRS conditions, in OWL FSS (Prolog notation)
  144drs_to_owlswrl(Drs, Owl) :-
  145	ontology_iri(IRI),
  146	drs_to_owlswrl(Drs, IRI, Owl).
  147
  148drs_to_owlswrl(Drs, IRI, Owl) :-
  149	drs_to_owlswrl(Drs, IRI, 'Ontology from an ACE text.', Owl).
  150
  151drs_to_owlswrl(Drs, IRI, Comment, 'Ontology'(IRI, Axioms)) :-
  152	debug(sentence, "ACE: ~w~n", [Comment]),
  153	drs_to_drslist(Drs, DrsList),
  154	maplist(drs_to_owlswrl_x, DrsList, AxiomList),
  155	append(AxiomList, Axioms).
  156
  157drs_to_owlswrl(_, _, _, 'Ontology'('', [])).
  158
  159
  160drs_to_owlswrl_x(Drs, Axioms) :-
  161	copy_term(Drs, DrsCopy),
  162	clear_messages(owl),
  163	drs_to_sdrs(DrsCopy, SDrsCopy),
  164	drs_to_owldrs(SDrsCopy, OwlDrs),
  165	numbervars(OwlDrs, 1, _),
  166	debug(owldrs, "OWL DRS: ~q~n", [OwlDrs]),
  167	drs_to_axioms(OwlDrs, Axioms),
  168	!.
  169
  170
  171% If the DRS corresponds to a DL-Query
  172drs_to_axioms(Drs, Axioms) :-
  173	process_question(Drs, Axioms).
  174
  175% If the DRS corresponds to a set of OWL and/or SWRL axioms
  176drs_to_axioms(Drs, Axioms) :-
  177	findall(
  178		ref_oneof(X, OneOf),
  179		(
  180			member(Condition, Drs),
  181			condition_oneof(Condition, X, OneOf)
  182		),
  183		RefList
  184	),
  185	debug(sentence, "Toplevel: ~w~n", [RefList]),
  186	condlist_axiomlist_with_cheat(Drs, RefList, AL),
  187	transform_anonymous(AL, Axioms).
  188
  189
  190% Only a single question is accepted, but it
  191% can be preceded and followed by declarative sentences.
  192% Examples:
  193% John owns a car. Mary owns the car. What is it?
  194% John owns a car. Mary owns the car. What is it? Bill sees the car.
  195% John owns a car. Mary owns the car. What is it? Bill sees John.
  196process_question(Conds, AxiomList) :-
  197	select(question(QConds), Conds, RConds),
  198	!,
  199	append(QConds, RConds, FlatConds),
  200	debug(d, "~w~n", [FlatConds]),
  201	clear_messages(owl),
  202	catch(
  203		(
  204			condlist_to_dlquery(FlatConds, Class),
  205			AxiomList = ['SubClassOf'(Class, owl:'Thing')]
  206		),
  207		Catcher,
  208		(
  209			AxiomList = [],
  210			parse_exception(Catcher, Message, Lemma, SId/TId),
  211			add_error_message(owl, SId-TId, Lemma, Message)
  212		)
  213	).
  214
  215parse_exception(error(Message, context(_Pred, query(_, Lemma)-Id)), Message, Lemma, Id) :- !.
  216parse_exception(error(Message, context(_Pred, _Arg)), Message, '', ''/'').
 ontology_iri(?IRI:atom)
Arguments:
IRI- is the prefix for ACE words used as OWL names
  223ontology_iri('http://attempto.ifi.uzh.ch/ontologies/owlswrl/test')