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_owlswrl_core, [
   17		condlist_to_dlquery/2,
   18		condition_oneof/3,
   19		condlist_axiomlist_with_cheat/3,
   20		condlist_and/4,
   21		is_toplevel/3,
   22		get_entity/3,
   23		has_dom_for_member/3,
   24		is_object_with_generalized_quantifier/1,
   25		dataitem_datavalue_datatypeuri/3
   26	]).

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
- 2013-04-08
license
- LGPLv3

*/

   45:- use_module('../../logger/error_logger', [
   46		add_error_message/4
   47	]).   48
   49:- use_module(implication_to_swrl, [
   50		implication_to_swrl/3
   51	]).   52
   53:- use_module(simplify_axiom, [
   54		simplify_axiom/2
   55	]).   56
   57:- use_module(illegal_conditions, [
   58		illegal_condition/1,
   59		illegal_conditions/1
   60	]).   61
   62
   63% Operators used in the DRS.
   64:- op(400, fx, -).   65:- op(500, xfx, =>).   66:- op(500, xfx, v).
 condition_oneof(+Condition:term, -Ref:term, -ObjectOneOf:term) is semidet
Note that this rule is only called for the top-level DRS conditions.
Arguments:
Condition- is a DRS (top-level) object-condition
Ref- is a discourse referent
ObjectOneOf- is OWL's ObjectOneOf construct that corresponds to the condition
bug
- Fix comments, we also return genquant/4 now
   79condition_oneof(object(X, Name, countable, na, QType, QNum)-_, X, genquant(X, Name, QType, QNum)) :-
   80	is_object_with_generalized_quantifier(object(_, Name, countable, na, QType, QNum)-_),
   81	!.
   82
   83condition_oneof(object(X, Name, countable, na, _, _)-_, X, 'ObjectOneOf'([nodeID(X)])) :-
   84	Name \= na.
   85
   86condition_oneof(object(X, something, dom, na, _, _)-_, X, 'ObjectOneOf'([nodeID(X)])).
 is_object_with_generalized_quantifier(+Condition:term) is semidet
Succeeds if the condition is an object-condition with certain QType and QNum arguments.

Note: "Name \= na" is there to reject NP conjunctions.

Arguments:
Condition- is a DRS condition
   97is_object_with_generalized_quantifier(object(_, Name, countable, na, QType, QNum)-_) :-
   98	Name \= na,
   99	(
  100		QNum > 1
  101	;
  102		QNum = 1, QType = exactly
  103	;
  104		QNum = 1, QType = leq
  105	;
  106		QNum = 1, QType = less
  107	;
  108		QNum = 1, QType = greater
  109	).
 condlist_axiomlist_with_cheat(+ConditionList:list, +RefList:list, -AxiomList:list) is semidet
Mapping from the DRS conditions' list to OWL axioms.
Arguments:
ConditionList- is a list of DRS conditions
RefList- is a list of top-level discourse referents
AxiomList- is a list of OWL axioms
bug
- We first cheat a bit, e.g. in case the DRS consists of certain conditions then they are mapped immediately to a class assertion. This avoids the anonymous individuals that are generated by the general solution.
- Also, sentences like "There are exactly 4 continents." are handled here.
  127% Try to roll up the complete DRS if contains a toplevel predicate with
  128% a proper name as an argument.
  129% E.g. John likes a woman.
  130% E.g. There is a woman that likes John and that owns a cat.
  131% E.g. John owns at least 2 fast cars.
  132%
  133% @tbd "A man owns at least 2 cars that a woman likes."
  134% i.e. toplevel DRS which does not contain proper names.
  135% Maybe it's better to do it using the 'there are...' technique.
  136condlist_axiomlist_with_cheat(
  137	CondList,
  138	_RefList,
  139	[SimplerAxiom]
  140) :-
  141	member(predicate(_, _, X1, X2)-_, CondList),
  142	(named(Name) = X1 ; named(Name) = X2),
  143	get_entity(named_individual, Name, Individual),
  144	condlist_and(named(Name), CondList, [], And),
  145	!,
  146	simplify_axiom('ClassAssertion'(And, Individual), SimplerAxiom).
  147
  148
  149% There are exactly 4 continents.
  150% <= Everything is contained by Universe. Universe contains exactly 4 continents.
  151% @bug: we shouldn't repeat the SubClassOf axiom, i.e. we could expect the client to contain it already.
  152% @bug: make 'there are' rules cover more complex DRSs, e.g. 'There are more than 3 rich men.'
  153% E.g. It is false that there are exactly 4 continents.
  154condlist_axiomlist_with_cheat(
  155	CondList,
  156	_,
  157	[
  158		'SubClassOf'(
  159			owl:'Thing',
  160			'ObjectSomeValuesFrom'(
  161				'ObjectInverseOf'(ObjectProperty),
  162				'ObjectOneOf'([Individual])
  163			)
  164		),
  165		'ClassAssertion'(Class, Individual)
  166	]
  167) :-
  168	there_are_object(CondList, PropertyRestriction, ThereAreObject, Class),
  169	get_universe(ThereAreObject, ObjectProperty, Individual, PropertyRestriction),
  170	!.
  171
  172
  173
  174% @bug Cheating ends here, we call condlist_axiomlist/3
  175condlist_axiomlist_with_cheat(ConditionList, RefList, AxiomList) :-
  176	condlist_axiomlist(ConditionList, RefList, AxiomList).
 condlist_axiomlist(+ConditionList:list, +RefList:list, -AxiomList:list) is semidet
Mapping from the DRS conditions' list to OWL axioms.
Arguments:
ConditionList- is a list of DRS conditions
RefList- is a list of top-level discourse referents
AxiomList- is a list of OWL axioms
  188% ConditionList is empty
  189condlist_axiomlist([], _, []).
  190
  191% Condition is successfully mapped to an Axiom
  192condlist_axiomlist([Condition | ConditionList], RefList, [SimplerAxiom | AxiomList]) :-
  193	condition_axiom(Condition, RefList, Axiom),
  194	!,
  195	simplify_axiom(Axiom, SimplerAxiom),
  196	condlist_axiomlist(ConditionList, RefList, AxiomList).
  197
  198% Condition is successfully mapped to a SWRL rule
  199condlist_axiomlist([Condition | ConditionList], RefList, [Axiom | AxiomList]) :-
  200	implication_to_swrl(Condition, RefList, Axiom),
  201	!,
  202	condlist_axiomlist(ConditionList, RefList, AxiomList).
  203
  204% BUG: experimental: ignore objects that have a generalized quantifier
  205condlist_axiomlist([Condition | ConditionList], RefList, AxiomList) :-
  206	is_object_with_generalized_quantifier(Condition),
  207	!,
  208	condlist_axiomlist(ConditionList, RefList, AxiomList).
  209
  210% A top-level condition that is not supported (e.g. has_part/2)
  211% is simply ignored, but an error message is asserted.
  212condlist_axiomlist([Condition | ConditionList], RefList, AxiomList) :-
  213	illegal_condition(Condition),
  214	!,
  215	condlist_axiomlist(ConditionList, RefList, AxiomList).
  216
  217% If mapping of Condition failed and if the condition
  218% was an if-then condition then we search for the exact location
  219% of the error.
  220% BUG: we should do the same for negation and disjunction
  221condlist_axiomlist([If => Then | CondList], RefList, AxiomList) :-
  222	select(object(X, _Value, _, na, _, _)-_, If, CondList1),
  223	condlist_classlist_err(X, CondList1, RefList),
  224	condlist_classlist_err(X, Then, RefList),
  225	!,
  226	add_error_message(owl, '', '', 'Text could not be translated.'),
  227	condlist_axiomlist(CondList, RefList, AxiomList).
  228
  229% If everything fails then set a general error message.
  230% BUG: Figure out the sentence ID at least.
  231condlist_axiomlist([_Condition | CondList], RefList, AxiomList) :-
  232	add_error_message(owl, '', '', 'Text could not be translated.'),
  233	condlist_axiomlist(CondList, RefList, AxiomList).
 condition_axiom(+Condition:term, +RefList:list, -Axiom:term) is semidet
Mapping the DRS conditions to OWL axioms. Note that each top-level condition maps to exactly one OWL axiom. This holds for the modified DRS where e.g. the relation-conditions have been removed and the implication corresponding to sentences like "If somebody X writes something Y then X is a writer and Y is a writing." have been split into 2 implications, correspoding to: Everybody who writes something is a writer." and "Everything that somebody writes is a writing."
Arguments:
Condition- is a DRS condition
RefList- is a list of top-level discourse referents
Axiom- is an OWL axiom
  252% Sublist
  253% E.g. John owns at most 2 cars.
  254condition_axiom(
  255	[Condition | ConditionList],
  256	RefList,
  257	'ClassAssertion'(SubListClass, Individual)
  258) :-
  259	condlist_and(D, [Condition | ConditionList], RefList, SubListClass),
  260	is_toplevel(D, RefList, 'ObjectOneOf'([Individual])).
  261
  262% Negation.
  263% E.g. John is not Mary., John does not like a man who owns at most 2 cars.
  264condition_axiom(
  265	-Not,
  266	RefList,
  267	'ClassAssertion'('ObjectComplementOf'(NotClass), Individual)
  268) :-
  269	condlist_and(D, Not, RefList, NotClass),
  270	is_toplevel(D, RefList, 'ObjectOneOf'([Individual])).
  271
  272% Disjunction
  273% E.g. John likes Mary or likes Bill.
  274condition_axiom(
  275	Or1 v Or2,
  276	RefList,
  277	'ClassAssertion'('ObjectUnionOf'([Or1Class, Or2Class]), Individual)
  278) :-
  279	condlist_and(D, Or1, RefList, Or1Class),
  280	condlist_and(D, Or2, RefList, Or2Class),
  281	is_toplevel(D, RefList, 'ObjectOneOf'([Individual])).
  282
  283% object/6 where Count = "dom" or "countable"
  284% and which is created during preprocessing, e.g.
  285%
  286% object(named('John'), man, countable, na, eq, 1)-_
  287%
  288condition_axiom(
  289	object(named(ProperName), Name, Count, na, QType, QNum)-_,
  290	_,
  291	'ClassAssertion'(NamedClass, Individual)
  292) :-
  293	memberchk(Count, [countable, dom]),
  294	memberchk(QType, [eq, geq, na]),
  295	memberchk(QNum, [1, na]),
  296	get_entity(named_individual, ProperName, Individual),
  297	get_entity(class, Name, NamedClass).
  298
  299% object/6 where Count = "dom" or "countable"
  300% E.g. man ...
  301% Common nouns are mapped to
  302% OWL anonymous individuals identified by Ref and typed by Name.
  303condition_axiom(
  304	object(Ref, Name, Count, na, QType, QNum)-_,
  305	_,
  306	'ClassAssertion'(NamedClass, nodeID(Ref))
  307) :-
  308	memberchk(Count, [countable, dom]),
  309	memberchk(QType, [eq, geq, na]),
  310	memberchk(QNum, [1, na]),
  311	get_entity(class, Name, NamedClass).
  312
  313% Property between an Individual and a Literal (DataProperty).
  314% E.g.: John's age is 30., John's address is "Poland".
  315condition_axiom(
  316	predicate(_, Predicate, Ref, DataItem)-_,
  317	RefList,
  318	'DataPropertyAssertion'(DataProperty, Name, '^^'(DataValue, DataTypeUri))
  319) :-
  320	is_toplevel(Ref, RefList, 'ObjectOneOf'([Name])),
  321	get_entity(data_property, Predicate, DataProperty),
  322	dataitem_datavalue_datatypeuri(DataItem, DataValue, DataTypeUri).
  323
  324% predicate(_, be, Ref1, Ref2)
  325%
  326% The copula-predicate maps to the SameIndividual-axiom.
  327%
  328% E.g. John is Mary.
  329condition_axiom(
  330	predicate(_, be, Ref1, Ref2)-_,
  331	RefList,
  332	'SameIndividual'([Name1, Name2])
  333) :-
  334	is_toplevel(Ref1, RefList, 'ObjectOneOf'([Name1])),
  335	is_toplevel(Ref2, RefList, 'ObjectOneOf'([Name2])).
  336
  337% predicate(_, _, Ref1, Ref2)
  338%
  339% All the remaining predicates map to ObjectPropertyAssertion.
  340%
  341% E.g. John likes Mary.
  342%
  343condition_axiom(
  344	predicate(_, Predicate, Ref1, Ref2)-_,
  345	RefList,
  346	'ObjectPropertyAssertion'(ObjectProperty, Name1, Name2)
  347) :-
  348	Predicate \= be,
  349	get_entity(object_property, Predicate, ObjectProperty),
  350	is_toplevel(Ref1, RefList, 'ObjectOneOf'([Name1])),
  351	is_toplevel(Ref2, RefList, 'ObjectOneOf'([Name2])).
  352
  353% predicate(_, _, Ref1, Ref2) with generalized quantifier
  354% E.g. A man owns at least 2 cars.
  355% BUG: incorrectly handles: A man owns at least 2 cars that a woman likes.
  356condition_axiom(
  357	predicate(_, Predicate, Ref1, Ref2)-_,
  358	RefList,
  359	'ClassAssertion'(PropertyRestriction, Name1)
  360) :-
  361	Predicate \= be,
  362	is_toplevel(Ref1, RefList, 'ObjectOneOf'([Name1])),
  363	is_toplevel(Ref2, RefList, genquant(_, Name, QType, QNum)),
  364	get_entity(class, Name, NamedClass),
  365	get_entity(object_property, Predicate, ObjectProperty),
  366	make_restr(QType, QNum, ObjectProperty, NamedClass, PropertyRestriction).
  367
  368% Implication that maps to a SubObjectProperty-axiom
  369%
  370% E.g. If somebody X loves somebody Y then X likes Y.
  371%
  372% BUG: add: then-part contains inverse. (Not needed really, but maybe adds readability.)
  373%
  374% Note: the chain must not be empty!
  375condition_axiom(
  376	If => [predicate(_, Predicate, Ref1, RefN)-_],
  377	_,
  378	'SubObjectPropertyOf'('ObjectPropertyChain'(SubObjectPropertyChain), ObjectProperty)
  379) :-
  380	Predicate \= be,
  381	has_dom_for_member(Ref1, If, CondList1),
  382	is_chain(Ref1, RefN, CondList1, SubObjectPropertyChain),
  383	SubObjectPropertyChain = [_ | _],
  384	get_entity(object_property, Predicate, ObjectProperty).
  385
  386% Implication that maps to a DisjointObjectProperties-axiom
  387%
  388% E.g. If somebody X loves somebody Y then it is false that X hates Y.
  389%
  390% Note: the chain must contain exactly 1 element.
  391condition_axiom(
  392	If => [-[predicate(_, Property2, Ref1, RefN)-_]],
  393	_,
  394	'DisjointObjectProperties'([Property1, ObjectProperty])
  395) :-
  396	Property2 \= be,
  397	has_dom_for_member(Ref1, If, CondList1),
  398	get_entity(object_property, Property2, ObjectProperty),
  399	is_chain(Ref1, RefN, CondList1, [Property1]).
  400
  401% Implication that maps to a SubClassOf-axiom
  402%
  403% Examples:
  404%
  405% Every man is an animal and likes a dog and ...
  406% Every man who owns a car is a driver.
  407%
  408% This is by far the most complicated case to handle.
  409condition_axiom(
  410	If => Then,
  411	RefList,
  412	'SubClassOf'(IfClass, ThenClass)
  413) :-
  414	condlist_if(X, If, RefList, IfClass),
  415	condlist_and(X, Then, RefList, ThenClass).
 is_chain(+Ref1:nvar, +RefN:nvar, +CondList:list, -SubObjectPropertyChain:list) is semidet
Arguments:
Ref1- is a discourse referent of the first object in the chain
RefN- is a discourse referent of the last object in the chain
CondList- is a list of DRS conditions
SubObjectPropertyChain- is a list of OWL property descriptions in the chain-order
  425is_chain(Ref, Ref, [], []).
  426
  427is_chain(Ref1, RefN, CondList, [ObjectProperty | Chain]) :-
  428	select(predicate(_, Property, Ref1, Tmp)-_, CondList, CondList1),
  429	Property \= be,
  430	get_entity(object_property, Property, ObjectProperty),
  431	has_dom_for_member(Tmp, CondList1, CondList2),
  432	is_chain(Tmp, RefN, CondList2, Chain).
  433
  434is_chain(Ref1, RefN, CondList, ['ObjectInverseOf'(ObjectProperty) | Chain]) :-
  435	select(predicate(_, Property, Tmp, Ref1)-_, CondList, CondList1),
  436	Property \= be,
  437	get_entity(object_property, Property, ObjectProperty),
  438	has_dom_for_member(Tmp, CondList1, CondList2),
  439	is_chain(Tmp, RefN, CondList2, Chain).
 has_dom_for_member(+Ref:nvar, +CondListIn:list, -CondListOut:list) is nondet
Given a discourse referent, selects its corresponding object condition, given that it corresponds to an indefinite pronoun ('somebody' or 'something') or the noun 'thing'.
Arguments:
Ref- is a discourse referent
CondListIn- is a list of DRS conditions
CondListOut- is the remaining list of DRS conditions (after select/3)
  452has_dom_for_member(Ref, CondListIn, CondListOut) :-
  453	select(object(Ref, Name, Count, na, QType, QNum)-_, CondListIn, CondListOut),
  454	(
  455		Name = something, Count = dom
  456	;
  457		Name = somebody, Count = countable
  458	;
  459		Name = thing, Count = countable, QType = eq, QNum = 1
  460	).
 condlist_if(+D:nvar, +CondList:list, +RefList:list, -If:term) is nondet
Rolling up the IF-box. Before the actual rolling starts we select the distinguished variable which can be either a proper name or the object/6 variable.

Example (where only a proper name is distinguished):

 If there is a protein that activates Met then Met follows a gene.
Arguments:
D- is a distinguished discourse referent (the "subject" of an if-then sentence)
CondList- is a list of DRS conditions in the if-part
RefList- is a list of top-level discourse referents
If- is an OWL class description which is the left-side element of the resulting SubClassOf-axiom
  480condlist_if(D, CondList, RefList, If) :-
  481	member(predicate(_, _, X1, X2)-_, CondList),
  482	(D = X1 ; D = X2),
  483	is_toplevel(D, RefList, 'ObjectOneOf'([Individual])),
  484	condlist_and(D, CondList, RefList, 'ObjectOneOf'([Individual]), If).
  485
  486
  487condlist_if(D, CondListIn, RefList, If) :-
  488	select(object(D, Name, _, na, QType, QNum)-_, CondListIn, CondListOut),
  489	get_entity(class, Name, NamedClass),
  490	(
  491		QType = eq, QNum = 1
  492	;
  493		QType = na, QNum = na
  494	),
  495	condlist_and(D, CondListOut, RefList, NamedClass, If).
 condlist_and(+D:nvar, +CondList:list, +RefList:list, -And:term) is nondet
 condlist_and(+D:nvar, +CondList:list, +RefList:list, -Desc:term, -And:term) is nondet
Arguments:
D- is a distinguished discourse referent (the "subject" of an if-then sentence)
CondList- is a list of DRS conditions (under negation, disjunction, or then-box)
RefList- is a list of top-level discourse referents
Desc- is an OWL class description to be inserted into the intersection
And- is an OWL class description (possibly a named class)
  507condlist_and(D, CondList, RefList, And) :-
  508	condlist_classlist(D, CondList, RefList, DescriptionList),
  509	create_intersection(DescriptionList, And).
  510
  511condlist_and(D, CondList, RefList, Desc, And) :-
  512	condlist_classlist(D, CondList, RefList, DescriptionList),
  513	create_intersection([Desc | DescriptionList], And).
 condlist_classlist(+D:nvar, +CondList:list, +RefList:list, -ClassList:list) is nondet
Map all the conditions in the list to corresponding OWL classes, i.e. no condition must be left unmapped.
Arguments:
D- is a discourse referent
CondList- is a list of DRS conditions
RefList- is a list of top-level discourse referents
ClassList- is a list of OWL class descriptions
  526condlist_classlist(_D, [], _RefList, []).
  527
  528condlist_classlist(D, CondList, RefList, [And1Class | And2Class]) :-
  529	select(Condition, CondList, CondList1),
  530	condlist_class(D, Condition, CondList1, RefList, And1Class, CondList2),
  531	condlist_classlist(D, CondList2, RefList, And2Class).
 condlist_classlist_err(+D:nvar, +CondList:list, +RefList:list) is nondet
These rules are here solely for error capture.
Arguments:
D- is a discourse referent
CondList- is a list of DRS conditions
RefList- is a list of top-level discourse referents
bug
- This error capture is not complete, e.g. we can't see inside embedded DRSs.
  545condlist_classlist_err(_D, [], _RefList) :- !.
  546
  547condlist_classlist_err(D, CondList, RefList) :-
  548	select(Condition, CondList, CondList1),
  549	condlist_class(D, Condition, CondList1, RefList, _, CondList2),
  550	!,
  551	condlist_classlist_err(D, CondList2, RefList).
  552
  553% If condlist_class/5 failed then there must be a problem that
  554% we want to report.
  555condlist_classlist_err(_D, CondList, _RefList) :-
  556	illegal_conditions(CondList).
 condlist_class(+D:nvar, Condition:term, +CondListIn:list, +RefList:list, +Class:term, -CondListOut:list) is nondet
Note that we allow inverting the arguments of copula 'be', i.e. we consider the following equivalent:
 If a man likes somebody that is a person then the person owns a car.
 If a man likes a person that is a somebody then the person owns a car.
 If a man is John then the man is a person.
 If John is a man then the man is a person.

This is similar to inverting the arguments of regular verbs, but while for regular verbs the Property changes into 'ObjectInverseOf'(PropertyName), the copula arguments are simply switched with no trace left behind.

Arguments:
D- is a discourse referent
Condition- is a DRS condition
CondListIn- is a list of DRS conditions
RefList- is a list of top-level discourse referents
Class- is an OWL class description
CondListOut- is a list of remaining DRS conditions
  587% Copula ('be') predicate
  588% Every man is John.
  589% Every man is a human.
  590% Every man is something.
  591% All grass is some food.
  592% * Every man is at most 3 cars.
  593condlist_class(D, predicate(_, be, Subj, Obj)-_, CondList, RefList, EmbeddedClass, CondList2) :-
  594	(
  595		Subj = D, Obj = NewD
  596	;
  597		Obj = D, Subj = NewD
  598	),
  599	select_object(NewD, CondList, RefList, NamedClass, QType, QNum, CondList1),
  600	(
  601		QType = eq, QNum = 1
  602	;
  603		QType = na, QNum = na
  604	),
  605	follow_object(NewD, NamedClass, CondList1, RefList, EmbeddedClass, CondList2).
  606
  607% Regular predicate with reflexive object
  608% Every man likes himself.
  609condlist_class(D, predicate(_, Property, D, D)-_, CondList, _RefList, 'ObjectHasSelf'(ObjectProperty), CondList) :-
  610	Property \= be,
  611	get_entity(object_property, Property, ObjectProperty).
  612
  613% Regular predicate with data object
  614% Every man's age is 20.
  615condlist_class(D, predicate(_, Property, D, DataItem)-_, CondList, _RefList, 'DataHasValue'(DataProperty, '^^'(DataValue, DataTypeUri)), CondList) :-
  616	Property \= be,
  617	get_entity(data_property, Property, DataProperty),
  618	dataitem_datavalue_datatypeuri(DataItem, DataValue, DataTypeUri).
  619
  620% Regular predicate with a dist. variable
  621% Every man likes a woman.
  622condlist_class(D, predicate(_, PropertyName, D, Obj)-_, CondList, RefList, Class, CondList2) :-
  623	PropertyName \= be,
  624	select_object(Obj, CondList, RefList, NamedClass, QType, QNum, CondList1),
  625	follow_object(Obj, NamedClass, CondList1, RefList, EmbeddedClass, CondList2),
  626	get_entity(object_property, PropertyName, ObjectProperty),
  627	make_restr(QType, QNum, ObjectProperty, EmbeddedClass, Class).
  628
  629% Regular predicate with a dist. variable, inverted case
  630% Every man is liked by a woman.
  631condlist_class(D, predicate(_, PropertyName, Subj, D)-_, CondList, RefList, Class, CondList2) :-
  632	PropertyName \= be,
  633	select_object(Subj, CondList, RefList, NamedClass, QType, QNum, CondList1),
  634	follow_object(Subj, NamedClass, CondList1, RefList, EmbeddedClass, CondList2),
  635	get_entity(object_property, PropertyName, ObjectProperty),
  636	make_restr(QType, QNum, 'ObjectInverseOf'(ObjectProperty), EmbeddedClass, Class).
  637
  638% Sublist
  639% Every man owns at most 2 cars.
  640condlist_class(D, [Condition | ConditionList], CondList, RefList, SubListClass, CondList) :-
  641	condlist_and(D, [Condition | ConditionList], RefList, SubListClass).
  642
  643% Negation
  644% Every man is not a table.
  645condlist_class(D, -Not, CondList, RefList, 'ObjectComplementOf'(NotClass), CondList) :-
  646	condlist_and(D, Not, RefList, NotClass).
  647
  648% Disjunction
  649% Every man is policeman or is not a table.
  650condlist_class(D, Or1 v Or2, CondList, RefList, 'ObjectUnionOf'([Or1Class, Or2Class]), CondList) :-
  651	condlist_and(D, Or1, RefList, Or1Class),
  652	condlist_and(D, Or2, RefList, Or2Class).
 select_object(+D:nvar, +CondListIn:list, +RefList:list, -NamedClass:term, -QType:atom, -QNum:atomic, -CondListOut:list) is nondet
Arguments:
D- is a distinguished discourse referent
CondListIn- is a list of DRS conditions
RefList- is a list of top-level discourse referents
NamedClass- is either Class or ObjectOneOf([_])
QType- is in {na, eq, geq, leq, greater, less, exactly}
QNum- is a positive integer or 'na' (not available)
CondListOut- is a list of remaining DRS conditions
  665select_object(D, CondList, RefList, 'ObjectOneOf'([Individual]), eq, 1, CondList) :-
  666	is_toplevel(D, RefList, 'ObjectOneOf'([Individual])).
  667
  668select_object(D, CondListIn, _RefList, NamedClass, QType, QNum, CondListOut) :-
  669	select(object(D, Name, _, na, QType, QNum)-_, CondListIn, CondListOut),
  670	get_entity(class, Name, NamedClass).
 follow_object(+D:nvar, +NamedClass:atom, +CondListIn:list, +RefList:list, -Class:term, -CondListOut:list) is semidet
 follow_object_(+D:nvar, +CondListIn:list, +RefList:list, -ClassList:list, -CondListOut:list) is semidet
We first try to build a complete class-list (and consume all the conditions).
  1. If this succeeds then the returned class-list is either empty or not. 1.1. In case of an empty class-list, Class is simply a named class. 1.2. In case of a non-empty class-list, Class is an intersection with the named class as the first element.
  2. If building the complete class-list fails (i.e. some conditions are not consumed) then we try to build just one class description. 2.1 If this succeeds then we might be able to build some more, i.e. we call follow_object_/5 recursively 2.1.1 If building some more fails then we return the remaining conditions. 2.2 If building just one class description fails, then we return the named class.

    @param D is a distinguished discourse referent @param NamedClass is either Class or ObjectOneOf([_]) @param CondListIn is a list of DRS conditions @param RefList is a list of top-level discourse referents @param Class is an OWL class expression @param CondListOut is a list of remaining DRS conditions

  695follow_object(D, NamedClass, CondList, RefList, Class, CondListOut) :-
  696	follow_object_(D, CondList, RefList, ClassList, CondListOut),
  697	create_intersection([NamedClass | ClassList], Class).
  698
  699follow_object_(D, CondList, RefList, ClassListOut, CondListOut) :-
  700	(
  701		condlist_classlist(D, CondList, RefList, ClassList)
  702	->
  703		ClassListOut = ClassList,
  704		CondListOut = []
  705	;
  706		(
  707			(
  708				select(Condition, CondList, CondList1),
  709				condlist_class(D, Condition, CondList1, RefList, Class1, CondList2)
  710			)
  711		->
  712			(
  713				follow_object_(D, CondList2, RefList, ClassList2, CondList3)
  714			->
  715				ClassListOut = [Class1 | ClassList2],
  716				CondListOut = CondList3
  717			;
  718				ClassListOut = [Class1],
  719				CondListOut = CondList2
  720			)
  721		;
  722			ClassListOut = [],
  723			CondListOut = CondList
  724		)
  725	).
 create_intersection(+ClassList:list, -Intersection:term) is det
Constructs the OWL intersection expression from a given list of class expressions. Simplifies the expression by removing owl:Thing if possible. owl:Thing is expected to be in the beginning of the list.
Arguments:
ClassList- is a list of class expressions
Intersection- is an OWL intersection expression
  737create_intersection([Class], Class) :- !.
  738
  739create_intersection([owl:'Thing' | ClassList], Class) :-
  740	!,
  741	create_intersection(ClassList, Class).
  742
  743create_intersection(ClassList, 'ObjectIntersectionOf'(ClassList)).
 is_toplevel(+Ref:nvar, +RefList:list, -ObjectOneOf:term)
Succeeds if Ref is among the top-level referents (i.e. it corresponds to a proper name or to a common noun that is not under negation, disjunction, or implication).
Arguments:
Ref- is a discourse referent
RefList- is a list of top-level discourse referents
ObjectOneOf- is an OWL ObjectOneOf-class
  756is_toplevel(named(Name), _RefList, 'ObjectOneOf'([Individual])) :-
  757	!,
  758	get_entity(named_individual, Name, Individual).
  759
  760is_toplevel(Ref, RefList, ObjectOneOf) :-
  761	memberchk(ref_oneof(Ref, ObjectOneOf), RefList).
 make_restr(+QType:atom, +QNum:atomic, +Property:term, +Class:term, -Restriction:term) is semidet
Arguments:
QType- is in {na, eq, geq, leq, greater, less, exactly}
QNum- is a positive integer or 'na' (not available)
Property- is an OWL property description
Class- is an OWL class description
Restriction- is an OWL class description built from QType, QNum, Property, and Class
  772make_restr(na, na, Property, Class, 'ObjectSomeValuesFrom'(Property, Class)).
  773make_restr(eq, 1, Property, Class, 'ObjectSomeValuesFrom'(Property, Class)).
  774make_restr(geq, 1, Property, Class, 'ObjectSomeValuesFrom'(Property, Class)).
  775make_restr(eq, QNum, Property, Class, 'ObjectMinCardinality'(QNum, Property, Class)) :-
  776	integer(QNum),
  777	QNum > 1.
  778make_restr(geq, QNum, Property, Class, 'ObjectMinCardinality'(QNum, Property, Class)) :-
  779	integer(QNum),
  780	QNum > 1.
  781make_restr(leq, QNum, Property, Class, 'ObjectMaxCardinality'(QNum, Property, Class)) :-
  782	integer(QNum).
  783make_restr(exactly, QNum, Property, Class, 'ObjectExactCardinality'(QNum, Property, Class)) :-
  784	integer(QNum).
  785make_restr(less, QNum, Property, Class, 'ObjectMaxCardinality'(Num, Property, Class)) :-
  786	integer(QNum),
  787	Num is QNum - 1.
  788make_restr(greater, QNum, Property, Class, 'ObjectMinCardinality'(Num, Property, Class)) :-
  789	integer(QNum),
  790	Num is QNum + 1.
 get_entity(+Name:atom, +NS:atom, -Individual:term) is semidet
 get_entity(+Name:atom, -Individual:term) is semidet
Arguments:
Name- is the name of the individual
NS- is a namespace identifier
Individual- is a named individual
  801get_entity(class, ThingWord, owl:'Thing') :-
  802	is_thing_word(ThingWord),
  803	!.
  804
  805% Wordform is mapped to a full IRI
  806get_entity(_Type, iri(Iri), Iri) :-
  807	atom(Iri),
  808	!.
  809
  810% BUG: this is a temporary solution, use iri/1 instead
  811get_entity(_Type, IriAsAtom, Iri) :-
  812	atom(IriAsAtom),
  813	atom_concat('iri|', Iri, IriAsAtom),
  814	!.
  815
  816% default namespace
  817get_entity(Type, Name, Entity) :-
  818	get_entity(Type, Name, '', Entity).
  819
  820% given namespace
  821get_entity(_Type, Name, NS, NS:Name) :-
  822	atom(Name).
 is_thing_word
  828is_thing_word(something).
  829is_thing_word(somebody).
  830is_thing_word(thing).
 datatype_datatypeuri(+DataType:atom, -DataTypeUri:atom) is semidet
Arguments:
DataType- is a DRS datatype, currently in {integer, string, real}
DataTypeUri- is the corresponding XMLSchema datatype URI
  838datatype_datatypeuri(integer, 'http://www.w3.org/2001/XMLSchema#integer').
  839datatype_datatypeuri(string, 'http://www.w3.org/2001/XMLSchema#string').
  840datatype_datatypeuri(real, 'http://www.w3.org/2001/XMLSchema#double').
 dataitem_datavalue_datatypeuri(+DataItem:term, -DataValue:term, -DataTypeUri:atom) is semidet
Arguments:
DataItem- is an ACE data-item (e.g. int(10), real(3.14), string('Go!'))
DataValue- is an ACE data-value (e.g. 10, 3.14, 'Go!')
DataTypeUri- is the corresponding XMLSchema datatype URI
  849dataitem_datavalue_datatypeuri(string(DataValue), DataValue, DataTypeUri) :-
  850	datatype_datatypeuri(string, DataTypeUri).
  851
  852dataitem_datavalue_datatypeuri(int(DataItem), DataItem, DataTypeUri) :-
  853	datatype_datatypeuri(integer, DataTypeUri).
  854
  855dataitem_datavalue_datatypeuri(real(DataItem), DataItem, DataTypeUri) :-
  856	datatype_datatypeuri(real, DataTypeUri).
 condlist_to_dlquery(+CondList:term, -ClassExpression:term) is semidet
Converts a list of DRS conditions into an OWL class expression. The DRS must have undergone: drs_to_sdrs, numbervars, drs_to_owldrs.
Arguments:
CondList- is a list of DRS conditions
ClassExpression- is an OWL class expression in OWL FSS (Prolog notation)

Ex: John does not see what?

  868condlist_to_dlquery([-Conds], ClassExpression) :-
  869	(
  870		select(query(QVar, _)-_, Conds, RemainingConds)
  871	->
  872		condlist_to_dlquery(QVar, [-RemainingConds], ClassExpression)
  873	;
  874		throw(error('Yes/no queries not supported', context(condlist_to_dlquery/2, Conds)))
  875	),
  876	!.
  877
  878condlist_to_dlquery(Conds, ClassExpression) :-
  879	(
  880		select(query(QVar, _)-_, Conds, RemainingConds)
  881	->
  882		condlist_to_dlquery(QVar, RemainingConds, ClassExpression)
  883	;
  884		throw(error('Yes/no queries not supported', context(condlist_to_dlquery/2, Conds)))
  885	),
  886	!.
  887
  888condlist_to_dlquery(Conds, _) :-
  889	throw(error('Query not supported', context(condlist_to_dlquery/2, Conds))).
 condlist_to_dlquery(+QVar:nvar, +Conds:list, -ClassExpression:term) is semidet
Converts a list of DRS conditions into an OWL class expression. The DRS must have undergone: drs_to_sdrs, numbervars, drs_to_owldrs.
Arguments:
QVar- Query variable, e.g. X in query(X, who)
CondList- is a list of DRS conditions
ClassExpression- is an OWL class expression in OWL FSS (Prolog notation)
  901condlist_to_dlquery(QVar, Conds, ClassExpression) :-
  902	(
  903		memberchk(query(Var, Lemma)-Id, Conds)
  904	->
  905		throw(error('Queries with multiple query words not supported', context(condlist_to_dlquery/3, query(Var, Lemma)-Id)))
  906	;
  907		condlist_and(QVar, Conds, [], ClassExpression)
  908	).
 get_universe
Constructs the convention for expressing "there are at least N ..."
  915get_universe(object(X, Noun, NotNamed, na, QType, QNum)-_,
  916		ObjectProperty, Individual, PropertyRestriction) :-
  917	is_object_with_generalized_quantifier(object(X, Noun, NotNamed, na, QType, QNum)-_),
  918	X \= named(_),
  919	get_entity(class, Noun, Class),
  920	get_universe(QType, QNum, Class, ObjectProperty, Individual, PropertyRestriction).
  921
  922
  923get_universe(QType, QNum, Class, ObjectProperty, Individual, PropertyRestriction) :-
  924	get_entity(object_property, 'contain', ace, ObjectProperty),
  925	get_entity(named_individual, 'Universe', ace, Individual),
  926	make_restr(QType, QNum, ObjectProperty, Class, PropertyRestriction).
 there_are_object
Handles simple DRSs that are derived from sentences:
[it is false that] there are (at least | at most | more than | ...) N noun .
  935there_are_object([object(X, Noun, NotNamed, na, QType, QNum)-_],
  936	R, object(X, Noun, NotNamed, na, QType, QNum)-_, R).
  937there_are_object([[object(X, Noun, NotNamed, na, QType, QNum)-_]],
  938	R, object(X, Noun, NotNamed, na, QType, QNum)-_, R).
  939there_are_object([-[object(X, Noun, NotNamed, na, QType, QNum)-_]],
  940	R, object(X, Noun, NotNamed, na, QType, QNum)-_, 'ObjectComplementOf'(R)).
  941there_are_object([-[[object(X, Noun, NotNamed, na, QType, QNum)-_]]],
  942	R, object(X, Noun, NotNamed, na, QType, QNum)-_, 'ObjectComplementOf'(R)).
  943
  944/*
  945Generalize there_are_object to support 'there are at least 3 rich men that ...'.
  946Something like this:
  947
  948	select(object(X, Noun, NotNamed, na, QType, QNum)-_, CondList, CondListRest),
  949	is_object_with_generalized_quantifier(object(X, Noun, NotNamed, na, QType, QNum)-_),
  950	condlist_and(X, CondListRest, RefList, And),
  951	get_universe(QType, QNum, And, ObjectProperty, Individual, PropertyRestriction),
  952*/