1% This file is part of the Attempto Parsing Engine (APE).
    2% Copyright 2008-2013, 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_owldrs, [
   17		drs_to_owldrs/2
   18	]).   19
   20:- use_module(ape('utils/drs_ops'), [
   21		unary_drs_operator/1
   22	]).

DRS to OWL DRS converter

The DRS is converted to "OWL DRS" which is a more suitable format for the conversion into OWL. The input must be simplified DRS (drs_to_sdrs.pl) which has been numbervard. The following steps are made:

  1. Rewrite implication chains: A => (B => C) ~~> (A & B) => C.
  2. Rewrite embedded implications via conjunction and negations: A => B ~~> -(A & -B)
  3. Remove double negations: --A ~~> A
  4. Remove toplevel be-predicate-conditions
  5. Remove named-object-conditions, unify the corresponding discourse referents with named(ProperName)
  6. Rewrite certain conditions and sets of conditions:
   62% Operators used in the DRS.
   63:- op(400, fx, -).   64:- op(500, xfx, =>).   65:- op(500, xfx, v).
 drs_to_owldrs(+Drs:term, -OwlDrs:term) is det
Modifies the DRS to make it easier to convert in to OWL/SWRL.
Arguments:
Drs- is Attempto DRS
OwlDrs- is a modified Attempto DRS
   75drs_to_owldrs(Drs, OwlDrs) :-
   76	drs_to_owldrs(0, Drs, DrsTmp),
   77	exclude(is_named(DrsTmp), DrsTmp, OwlDrs).
 drs_to_owldrs(+Level:term, +Drs:term, -OwlDrs:term) is det
Modifies the DRS to make it easier to convert in to OWL/SWRL. The embedding-level is 0 for the top-level DRS-box, and grows by 0, l(0), l(l(0)), ...
Arguments:
Level- denotes the level of embedding of the DRS-box
Drs- is Attempto DRS
OwlDrs- is a modified Attempto DRS
   90drs_to_owldrs(_, [], []) :-
   91	!.
   92
   93% Double negation is removed
   94% --A == A
   95drs_to_owldrs(L, [-Drs | Conds], CondsAll) :-
   96	drs_to_owldrs(l(L), Drs, [-DrsR]),
   97	!,
   98	drs_to_owldrs(L, Conds, CondsR),
   99	append(DrsR, CondsR, CondsAll).
  100
  101drs_to_owldrs(L, [Drs | Conds], [NDrs | NConds]) :-
  102	functor(Drs, Op, 1),
  103	unary_drs_operator(Op),
  104	!,
  105	arg(1, Drs, DrsConds),
  106	drs_to_owldrs(l(L), DrsConds, NDrsConds),
  107	functor(NDrs, Op, 1),
  108	arg(1, NDrs, NDrsConds),
  109	drs_to_owldrs(L, Conds, NConds).
  110
  111
  112% Handle sentences like:
  113% For every thing X for every thing Y if X owns something that contains Y then X owns Y.
  114% BUG: maybe allow this for any level, i.e. not just 0
  115% BUG: this new handling changes the OWL representation of sentences 41, 115, 116, 117.
  116% Also, it makes sentences 66 and 67 correctly succeed as SRWL rules.
  117% Also, it would break sentence 57 "Every man likes no dog.", but we avoid this
  118% by requiring the embedded then-box not to be negated.
  119% But, then we reject this: For everything X for every thing Y if X likes Y then X does not hate Y.
  120% (although this could be mapped to property disjointness axiom).
  121%
  122% BUG: Think about all this in a more systematic way. (The rewriting is definitely
  123% correct, but it might harm completeness.)
  124drs_to_owldrs(0, [IfBox => [EmbeddedIfBox => EmbeddedThenBox] | Conds], DrsR) :-
  125	EmbeddedThenBox \= [-_],
  126	!,
  127	append(IfBox, EmbeddedIfBox, MergedIfAndEmbeddedIfBox),
  128	drs_to_owldrs(0, [MergedIfAndEmbeddedIfBox => EmbeddedThenBox | Conds], DrsR).
  129
  130%
  131% Toplevel implications are kept as they are.
  132%
  133drs_to_owldrs(0, [Drs1 => Drs2 | Conds], [Drs1R => Drs2R | CondsR]) :-
  134	!,
  135	drs_to_owldrs(l(0), Drs1, Drs1R),
  136	drs_to_owldrs(l(0), Drs2, Drs2R),
  137	drs_to_owldrs(0, Conds, CondsR).
  138
  139/*
  140% This is handled by the double negation removal rule.
  141% A => -B == -(A & B)
  142drs_to_owldrs(l(L), [IfBox => [-ThenBox] | Conds], DrsR) :-
  143	!,
  144	append(IfBox, ThenBox, IfThenBox),
  145	drs_to_owldrs(l(L), [-IfThenBox | Conds], DrsR).
  146*/
  147
  148
  149% Embedded implications are turned into double negations.
  150% A => B == -(A & -B)
  151drs_to_owldrs(l(L), [IfBox => ThenBox | Conds], DrsR) :-
  152	!,
  153	drs_to_owldrs(l(L), [-[-ThenBox | IfBox] | Conds], DrsR).
  154
  155drs_to_owldrs(L, [DRS1 v DRS2 | Conds], [DRS1R v DRS2R | CondsR]) :-
  156	!,
  157	drs_to_owldrs(l(L), DRS1, DRS1R),
  158	drs_to_owldrs(l(L), DRS2, DRS2R),
  159	drs_to_owldrs(L, Conds, CondsR).
  160
  161% list condition that expresses 'at most', 'less than', 'exactly'
  162drs_to_owldrs(L, [List | Conds], [ListR | CondsR]) :-
  163	is_list(List),
  164	!,
  165	drs_to_owldrs(L, List, ListR),
  166	drs_to_owldrs(L, Conds, CondsR).
  167
  168drs_to_owldrs(L, Conds, CondsR) :-
  169	rewrite_relation(Conds, FilteredConds),
  170	drs_to_owldrs(L, FilteredConds, CondsR).
  171
  172% (Fallback)
  173drs_to_owldrs(L, [Cond | Conds], [Cond | CondsR]) :-
  174	drs_to_owldrs(L, Conds, CondsR).
  175
  176
  177% of-constructions with data items
  178%
  179% John's age is 30.
  180% John's address is "Poland".
  181%
  182% BUG: those should be rejected I guess because data properties
  183% cannot have inverses. (This can be done later, by
  184% not allowing a data object to be a subject.)
  185%
  186% 30 is an age of John.
  187% "Poland" is an address of John.
  188%
  189% Note that in addition to relation/3 we also remove the object/6.
  190%
  191rewrite_relation(Conds, [predicate(C, PropertyName, A, DataItem)-SId/'' | FilteredConds]) :-
  192	remove_many([
  193		predicate(C, be, D1, DataItem)-SId/_,
  194		object(D2, PropertyName, countable, na, eq, 1)-SId/_,
  195		relation(D3, of, A)-SId/_
  196	], Conds, FilteredConds),
  197	D1 == D2, D2 == D3,
  198	is_dataitem(DataItem),
  199	!.
  200
  201rewrite_relation(Conds, [predicate(C, PropertyName, A, DataItem)-SId/'' | FilteredConds]) :-
  202	remove_many([
  203		predicate(C, be, DataItem, D1)-SId/_,
  204		object(D2, PropertyName, countable, na, eq, 1)-SId/_,
  205		relation(D3, of, A)-SId/_
  206	], Conds, FilteredConds),
  207	D1 == D2, D2 == D3,
  208	is_dataitem(DataItem),
  209	!.
  210
  211
  212% of-constructions without data items
  213%
  214% We handle differently the sentences with copula and without copula.
  215% The following sentences
  216%
  217% John's father is Bill.
  218% Bill is a father of John.
  219%
  220% will be represented as:
  221%
  222% PropertyAssertion(ObjectProperty(father), Individual(John), Individual(Bill))
  223%
  224rewrite_relation(Conds, [predicate(_, RelationalNoun, A, B)-SId/'' | FilteredConds]) :-
  225	remove_many([
  226		predicate(_, be, D1, B)-SId/_,
  227		object(D2, RelationalNoun, countable, na, eq, 1)-SId/_,
  228		relation(D3, of, A)-SId/_
  229	], Conds, FilteredConds),
  230	D1 == D2, D2 == D3,
  231	!.
  232
  233rewrite_relation(Conds, [predicate(_, RelationalNoun, A, B)-SId/'' | FilteredConds]) :-
  234	remove_many([
  235		predicate(_, be, B, D1)-SId/_,
  236		object(D2, RelationalNoun, countable, na, eq, 1)-SId/_,
  237		relation(D3, of, A)-SId/_
  238	], Conds, FilteredConds),
  239	D1 == D2, D2 == D3,
  240	!.
  241
  242% But the following sentences
  243%
  244% John's father likes Bill.
  245% Bill likes John's father.
  246%
  247% will be handled by keeping the object/6 in the returned list.
  248%
  249% PropertyAssertion(ObjectProperty(father), Individual(John), nodeID($VAR(2)))
  250% ClassAssertion(Class(owl:Thing), nodeID($VAR(2)))
  251%
  252% Some other tests:
  253%
  254% - John's brother likes everybody.
  255% - John's brother likes Mary. An age of the brother is 10.
  256% - Everybody's age is 31. (SWRL? Currently buggy.)
  257% - Everybody's address is "Poland". (SWRL? Currently buggy.)
  258% - Everybody's ancestor is Adam.
  259% - Everybody's ancestor is not Adam.
  260% - Every part of EU is a country.
  261%
  262% Note that one should be able to derive from "Every part of EU is a country. Estonia is a part of EU."
  263% that "Estonia is a country." without having to assert that "Estonia is a part."
  264% To make it possible we currently do not create a class "part", i.e. relational nouns
  265% only create properties.
  266%
  267% We used to return:
  268%
  269%==
  270% object(D, RelationalNoun, countable, na, eq, 1)-Id
  271%==
  272%
  273% But now we return:
  274%
  275%==
  276% object(D, something, dom, na, na, na)-Id
  277%==
  278%
  279rewrite_relation(Conds, [
  280	predicate(_, RelationalNoun, A, D1)-SId/'',
  281	object(D1, something, dom, na, na, na)-SId/''
  282	| FilteredConds]) :-
  283	remove_many([
  284		object(D1, RelationalNoun, countable, na, eq, 1)-SId/_,
  285		relation(D2, of, A)-SId/_
  286	], Conds, FilteredConds),
  287	D1 == D2.
  288
  289
  290% predicate/4
  291%
  292% Transitive and comparative adjectives (with arguments)
  293% are mapped to transitive verbs. This is debatable (and not reversible).
  294% BUG: We do not currently check the Degree of property/4.
  295% Note that it can be one of {pos, pos_as, comp, comp_than, sup}
  296% The outcome is that "John is as rich as Mary." == "John is richer than Mary."
  297% which is not wanted. I.e. one should use different property names and additionally
  298% assert disjointness of the properties.
  299%
  300% Examples:
  301%
  302% John is fond-of Mary.        # pos
  303% England is located-in UK.    # pos
  304% John is as rich as Mary.     # pos_as
  305% John is fonder-of Mary.      # comp
  306% John is taller than Mary.    # comp_than
  307% John is more rich than Mary. # comp_than
  308% John is fondest-of Mary.     # sup
  309
  310rewrite_relation(Conds, [predicate(RefPred, PropertyName, RefArg1, RefArg2)-SId/'' | FilteredConds]) :-
  311	remove_many([
  312		predicate(RefPred, be, RefArg1, RefRel1)-SId/_,
  313		property(RefRel2, PropertyName, _Degree, RefArg2)-SId/_
  314	], Conds, FilteredConds),
  315	RefRel1 == RefRel2.
  316
  317
  318% Which man ... ? --> What is a man that ... ?
  319% Turns plural into singular.
  320% BUG: turns mass into countable (can we have 'mass' with 'which' at all?)
  321%
  322% BUG: does not work: Which member of Attempto is a productive-developer?
  323rewrite_relation(Conds, [
  324		query(NewRef1, QueryWord)-SId/'',
  325		object(WhichRef1, Name, countable, na, eq, 1)-SId/'',
  326		predicate(_, be, NewRef1, WhichRef1)-SId/'' | FilteredConds]) :-
  327	remove_many([
  328		query(WhichRef1, QueryWord)-SId/_,
  329		object(WhichRef2, Name, _, na, _, _)-SId/_
  330	], Conds, FilteredConds),
  331	WhichRef1 == WhichRef2.
  332
  333
  334% Attributive positive adjectives
  335% E.g. Every man likes a red cat. -> Every man likes a cat that is a red.
  336rewrite_relation(Conds, [
  337	object(Ref1, Noun, Count, na, Eq, Num)-SId/TId,
  338	object(NewRef, Adj, countable, na, eq, 1)-SId/'',
  339	predicate(_, be, Ref1, NewRef)-SId/''
  340	| FilteredConds]) :-
  341	remove_many([
  342		object(Ref1, Noun, Count, na, Eq, Num)-SId/TId,
  343		property(Ref2, Adj, pos)-SId/_
  344	], Conds, FilteredConds),
  345	Ref1 == Ref2.
  346
  347% Predicative positive adjectives
  348% E.g. John is rich. -> John is a rich.
  349rewrite_relation(Conds, [
  350	object(Ref1, Adj, countable, na, eq, 1)-SId/'',
  351	predicate(PRef, be, Arg1, Ref1)-SId/TId
  352	| FilteredConds]) :-
  353	remove_many([
  354		property(Ref1, Adj, pos)-SId/_,
  355		predicate(PRef, be, Arg1, Ref2)-SId/TId
  356	], Conds, FilteredConds),
  357	Ref1 == Ref2.
 remove_many(+ConditionsToRemove:list, +AllConditions:list, RemainingConditions:list) is det
  363remove_many([], Conds, Conds).
  364
  365remove_many([H | T], Conds, FilteredConds) :-
  366	select(H, Conds, NewConds),
  367	remove_many(T, NewConds, FilteredConds).
 is_dataitem(+DataItem:term) is det
Succeeds if DataItem is an ACE int, real, or string.
Arguments:
DataItem- is an ACE data item (a number or a string)
  376is_dataitem(X) :-
  377	nonvar(X),
  378	is_dataitem_(X).
  379
  380is_dataitem_(int(_)).
  381is_dataitem_(real(_)).
  382is_dataitem_(string(_)).
 is_named(+CondList:list, +Condition:term)
This is used for excluding certain conditions in the top-level DRS.
bug
- is this still needed?
  392is_named(CondList, predicate(_, be, X, Y)-_) :-
  393	member(query(A, _)-_, CondList),
  394	(A == X ; A == Y),
  395	!,
  396	fail.
  397
  398% Filters out:
  399% John is a man.
  400% A man is a manager.
  401% A man is John.
  402% Note that the rule is so complex because we want to
  403% avoid filtering out numbers, strings, and the like.
  404/*
  405is_named(_, predicate(_, be, X, Y)-_) :-
  406	var(X),
  407	var(Y),
  408	!,
  409	X = Y.
  410*/
  411
  412% This filters out: John is John. (probably not wanted)
  413%is_named(_, predicate(_, be, named(N), named(N))-_).