1% This file is part of the Attempto Parsing Engine (APE).
    2% Copyright 2008-2013, Attempto Group, University of Zurich (see http://attempto.ifi.uzh.ch).
    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/.

Turning the DRS

Supporting module for the NPACE verbalizer. Switches the arguments of some transitive predicates found in implications.

author
- Kaarel Kaljurand
version
- 2008-03-16

TODO:

   31:- module(implication_turn, [
   32		implication_turn/2
   33	]).   34
   35
   36% Operators used in the DRS.
   37:- op(400, fx, -).   38:- op(400, fx, ~).   39:- op(500, xfx, =>).   40:- op(550, xfx, v).   41
   42%:- debug(verbose).
Arguments:
Implication- is DRS condition in the form Left => Right
ImplicationTurned- is DRS condition in the form Left => Right
   50implication_turn(Left => Right, ImplicationTurned) :-
   51	get_pred(0, _, Left => Right, _, ImplicationTurned).
   58drs_turn(_, S:S, [], _, []).
   59
   60drs_turn(Level, In:Out, Conds, Subj, [C | NewNewConds]) :-
   61	debug(verbose, 'turning DRS: ~w~n', [Conds]),
   62	select_predicate(Level, In:Tmp, Subj, Conds, C, NewConds),
   63	drs_turn(Level, Tmp:Out, NewConds, Subj, NewNewConds).
 select_predicate(Level, In:Out, Conds, C, RConds)
   69select_predicate(Level, In:Out, Subj, Conds, C, RConds) :-
   70	select(Cond, Conds, RConds),
   71	debug(verbose, 'selected condition: ~w~n', [Cond]),
   72	debug(verbose, 'remaining conditions: ~w~n', [RConds]),
   73	get_pred(Level, In:Out, Cond, Subj, C).
 get_pred(Level, SubjectIn:SubjectOut, Cond, NewCond)
   79get_pred(0, _, Drs1 => Drs2, _, [object(S, A, B, C, D, E)-Id | Drs1R] => Drs2R) :-
   80	!,
   81	select(object(S, A, B, C, D, E)-Id, Drs1, Drs1Out),
   82	drs_turn(l(0), S:_, Drs1Out, S, Drs1R),
   83	drs_turn(l(0), S:_, Drs2, S, Drs2R),
   84	debug(verbose, 'shared subj: ~w~n', [S]).
   85
   86get_pred(0, _, Drs1 v Drs2, _, Drs1R v Drs2R) :-
   87	!,
   88	drs_turn(l(0), S:_, Drs1, _, Drs1R),
   89	drs_turn(l(0), S:_, Drs2, _, Drs2R).
   90
   91get_pred(0, _, -Drs, _, -DrsR) :-
   92	!,
   93	drs_turn(l(0), _, Drs, _, DrsR).
   94
   95get_pred(0, _, ~Drs, _, ~DrsR) :-
   96	!,
   97	drs_turn(l(0), _, Drs, _, DrsR).
   98
   99get_pred(0, _, can(Drs), _, can(DrsR)) :-
  100	!,
  101	drs_turn(l(0), _, Drs, _, DrsR).
  102
  103get_pred(0, _, must(Drs), _, must(DrsR)) :-
  104	!,
  105	drs_turn(l(0), _, Drs, _, DrsR).
  106
  107get_pred(0, _, should(Drs), _, should(DrsR)) :-
  108	!,
  109	drs_turn(l(0), _, Drs, _, DrsR).
  110
  111get_pred(0, _, may(Drs), _, may(DrsR)) :-
  112	!,
  113	drs_turn(l(0), _, Drs, _, DrsR).
  114
  115get_pred(0, _, question(Drs), _, question(DrsR)) :-
  116	!,
  117	drs_turn(l(0), _, Drs, _, DrsR).
  118
  119get_pred(0, _, command(Drs), _, command(DrsR)) :-
  120	!,
  121	drs_turn(l(0), _, Drs, _, DrsR).
  122
  123% Simple toplevel conditions.
  124get_pred(0, _, Condition-Id, _, Condition-Id).
  125
  126
  127
  128get_pred(l(_), _:_, _ => _, _, _=> _) :-
  129	!,
  130	fail.
  131
  132get_pred(l(Level), S:S, Drs1 v Drs2, Subject, Drs1R v Drs2R) :-
  133	!,
  134	drs_turn(l(l(Level)), S:_, Drs1, Subject, Drs1R),
  135	drs_turn(l(l(Level)), S:_, Drs2, Subject, Drs2R).
  136
  137get_pred(l(Level), S:S, -Drs, Subject, -DrsR) :-
  138	!,
  139	drs_turn(l(l(Level)), S:_, Drs, Subject, DrsR).
  140
  141get_pred(l(Level), S:S, ~Drs, Subject, ~DrsR) :-
  142	!,
  143	drs_turn(l(l(Level)), S:_, Drs, Subject, DrsR).
  144
  145get_pred(l(Level), S:S, can(Drs), Subject, can(DrsR)) :-
  146	!,
  147	drs_turn(l(l(Level)), S:_, Drs, Subject, DrsR).
  148
  149get_pred(l(Level), S:S, must(Drs), Subject, must(DrsR)) :-
  150	!,
  151	drs_turn(l(l(Level)), S:_, Drs, Subject, DrsR).
  152
  153get_pred(l(Level), S:S, should(Drs), Subject, should(DrsR)) :-
  154	!,
  155	drs_turn(l(l(Level)), S:_, Drs, Subject, DrsR).
  156
  157get_pred(l(Level), S:S, may(Drs), Subject, may(DrsR)) :-
  158	!,
  159	drs_turn(l(l(Level)), S:_, Drs, Subject, DrsR).
  160
  161get_pred(l(Level), S:S, question(Drs), Subject, question(DrsR)) :-
  162	!,
  163	drs_turn(l(l(Level)), S:_, Drs, Subject, DrsR).
  164
  165get_pred(l(Level), S:S, command(Drs), Subject, command(DrsR)) :-
  166	!,
  167	drs_turn(l(l(Level)), S:_, Drs, Subject, DrsR).
  168
  169
  170
  171% Handling transitive verbs.
  172get_pred(l(_), S:S, predicate(Ref, Verb, S, O)-Id, _, predicate(Ref, Verb, S, O)-Id) :-
  173	debug(verbose, 'turning1: ~w :: ~w :: ~w~n', [S, Verb, S-O]).
  174
  175get_pred(l(_), S:S, predicate(Ref, Verb, O, S)-Id, _, predicate(Ref, i(Verb), S, O)-Id) :-
  176	Verb \= be,
  177	debug(verbose, 'turning2: ~w :: ~w~n', [S, Verb, O-S]).
  178
  179get_pred(l(_), S:O, predicate(Ref, Verb, S, O)-Id, _, predicate(Ref, Verb, S, O)-Id) :-
  180	debug(verbose, 'turning3: ~w :: ~w~n', [O, Verb, S-O]).
  181
  182get_pred(l(_), S:O, predicate(Ref, Verb, O, S)-Id, _, predicate(Ref, i(Verb), S, O)-Id) :-
  183	Verb \= be,
  184	debug(verbose, 'turning4: ~w :: ~w~n', [O, Verb, O-S]).
  185
  186
  187% Handling intransitive verbs.
  188get_pred(l(_), S:S, predicate(Ref, Verb, S)-Id, _, predicate(Ref, Verb, S)-Id) :-
  189	debug(verbose, 'intr subj: ~w~n', [Verb-S]).
  190
  191
  192
  193% Handling transitive verbs.
  194get_pred(l(_), _:S, predicate(Ref, Verb, S, O)-Id, S, predicate(Ref, Verb, S, O)-Id) :-
  195	debug(verbose, 'turning1: ~w :: ~w :: ~w~n', [S, Verb, S-O]).
  196
  197get_pred(l(_), _:S, predicate(Ref, Verb, O, S)-Id, S, predicate(Ref, i(Verb), S, O)-Id) :-
  198	Verb \= be,
  199	debug(verbose, 'turning2: ~w :: ~w~n', [S, Verb, O-S]).
  200
  201get_pred(l(_), _:O, predicate(Ref, Verb, S, O)-Id, S, predicate(Ref, Verb, S, O)-Id) :-
  202	debug(verbose, 'turning3: ~w :: ~w~n', [O, Verb, S-O]).
  203
  204get_pred(l(_), _:O, predicate(Ref, Verb, O, S)-Id, S, predicate(Ref, i(Verb), S, O)-Id) :-
  205	Verb \= be,
  206	debug(verbose, 'turning4: ~w :: ~w~n', [O, Verb, O-S]).
  207
  208
  209% Handling intransitive verbs.
  210get_pred(l(_), _:S, predicate(Ref, Verb, S)-Id, S, predicate(Ref, Verb, S)-Id) :-
  211	debug(verbose, 'intr subj: ~w~n', [Verb-S]).
  212
  213
  214
  215
  216% Simple deep conditions.
  217get_pred(l(_), S:S, Cond-Id, _, Cond-Id) :-
  218	Cond \= predicate(_, _, _),
  219	Cond \= predicate(_, _, _, _)