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:- module(illegal_conditions, [
   16		illegal_conditions/1,
   17		illegal_condition/1
   18	]).

DRS checker for DRS-to-OWL/SWRL

Setting some error messages for conditions which ACE->OWL/SWRL cannot handle.

author
- Kaarel Kaljurand
version
- 2010-12-14

TODO

  • add more detailed messages in case of property/[4,5,7]
  • paraphrase the DRS to deliver a nicer error message. DRS->ACE needs to support this though (i.e. the situation when the the DRS contains referents which are defined on the upper level).
  • Should error messages be given on the ACE level or on the DRS level? For the end user the ACE level is better, but on the other hand the input to ACE->OWL is the DRS (i.e. the module is actually doing DRS->OWL).

    */

   41:- use_module(ape('logger/error_logger'), [
   42		add_error_message/4
   43	]).   44
   45:- use_module(ape('utils/drs_ops'), [
   46		unary_drs_operator/1,
   47		binary_drs_operator/1
   48	]).   49
   50
   51% Operators used in the DRS.
   52:- op(400, fx, -).   53:- op(500, xfx, v).   54:- op(500, xfx, =>).
 illegal_conditions(+Conditions:list) is det
   60illegal_conditions([]).
   61
   62illegal_conditions([Cond | CondList]) :-
   63	illegal_condition(Cond),
   64	!,
   65	illegal_conditions(CondList).
 illegal_condition(BoxId, Cond, NewCond) is det
   72illegal_condition(relation(_, of, _)-SId/TId) :-
   73	add_error_message(owl, SId-TId, of, 'Possessive constructions not supported (in this particular case).').
   74
   75illegal_condition(modifier_adv(_, Adverb, _)-SId/TId) :-
   76	add_error_message(owl, SId-TId, Adverb, 'Adverbs not supported.').
   77
   78illegal_condition(modifier_pp(_, Preposition, _)-SId/TId) :-
   79	add_error_message(owl, SId-TId, Preposition, 'Prepositional phrases not supported.').
   80
   81% property/4 (comp adjective)
   82illegal_condition(property(_, Adjective, comp)-SId/TId) :-
   83	add_error_message(owl, SId-TId, Adjective, 'Comparative adjective not supported.').
   84
   85% property/4 (sup adjective)
   86illegal_condition(property(_, Adjective, sup)-SId/TId) :-
   87	add_error_message(owl, SId-TId, Adjective, 'Superlative adjective not supported.').
   88
   89% property/5 (comp_than adjective)
   90illegal_condition(property(_, Adjective, _, _)-SId/TId) :-
   91	add_error_message(owl, SId-TId, Adjective, 'Adjective not supported.').
   92
   93% property/7 (comp_than + subj/obj adjective)
   94illegal_condition(property(_, Adjective, _, _, _, _)-SId/TId) :-
   95	add_error_message(owl, SId-TId, Adjective, 'Adjective not supported.').
   96
   97illegal_condition(query(_, QueryWord)-SId/TId) :-
   98	add_error_message(owl, SId-TId, QueryWord, 'Query not supported.').
   99
  100illegal_condition(predicate(_, Verb, _)-SId/TId) :-
  101	add_error_message(owl, SId-TId, Verb, 'Intransitive verbs not supported.').
  102
  103illegal_condition(predicate(_, Verb, _, _, _)-SId/TId) :-
  104	add_error_message(owl, SId-TId, Verb, 'Ditransitive verbs not supported.').
  105
  106illegal_condition(must(Drs)) :-
  107	conds_sid(Drs, SId),
  108	add_error_message(owl, SId, 'must/1', 'Necessity not supported.').
  109
  110illegal_condition(can(Drs)) :-
  111	conds_sid(Drs, SId),
  112	add_error_message(owl, SId, 'can/1', 'Possibility not supported.').
  113
  114illegal_condition(_:Drs) :-
  115	conds_sid(Drs, SId),
  116	add_error_message(owl, SId, ':/2', 'Sentence subordination not supported.').
  117
  118illegal_condition('~'(Drs)) :-
  119	conds_sid(Drs, SId),
  120	add_error_message(owl, SId, '~/1', 'Negation-as-failure not supported.').
  121
  122illegal_condition(should(Drs)) :-
  123	conds_sid(Drs, SId),
  124	add_error_message(owl, SId, 'should/1', 'Recommendation not supported.').
  125
  126illegal_condition(may(Drs)) :-
  127	conds_sid(Drs, SId),
  128	add_error_message(owl, SId, 'may/1', 'Admissibility not supported.').
  129
  130% Note: do not do anything, NP conjunction ('na' as 2nd argument) is handled by the object-rule
  131illegal_condition(has_part(_, _)-_).
  132
  133illegal_condition(predicate(_, Value, _, _)-SId/TId) :-
  134	add_error_message(owl, SId-TId, Value, 'Subject or object of this verb makes an illegal reference.').
  135
  136illegal_condition(object(_, na, _, na, _, _)-SId/TId) :-
  137	!,
  138	add_error_message(owl, SId-TId, and, 'Noun phrase conjunctions not supported.').
  139
  140illegal_condition(object(_, Value, _, na, _, _)-SId/TId) :-
  141	Value \= na,
  142	!,
  143	add_error_message(owl, SId-TId, Value, 'A reference to this noun either does not exist or is illegal.').
  144
  145illegal_condition(object(_, _, _, Unit, _, _)-SId/TId) :-
  146	Unit \= na,
  147	add_error_message(owl, SId-TId, Unit, 'Measurement nouns are not supported.').
 conds_sid(+Conditions:list, -SentenceId:integer) is det
Finds the shared sentence ID of the conditions.
  154conds_sid([], _).
  155
  156conds_sid([_-SId/_TId | _], SId) :- !.
  157
  158conds_sid([C | Cs], SId) :-
  159	cond_sid(C, SId),
  160	conds_sid(Cs, SId).
  161
  162
  163cond_sid(Cond, SId) :-
  164	functor(Cond, F, 1),
  165	unary_drs_operator(F),
  166	!,
  167	arg(1, Cond, Drs),
  168	conds_id(Drs, SId).
  169
  170cond_id(_Label:Drs, SId) :-
  171	!,
  172	conds_id(Drs, SId).
  173
  174cond_id(Drs1 v Drs2, SId) :-
  175	!,
  176	conds_id(Drs1, SId),
  177	conds_id(Drs2, SId).
  178
  179cond_id(Drs1 => Drs2, SId) :-
  180	!,
  181	conds_id(Drs1, SId),
  182	conds_id(Drs2, SId)