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/.
   14
   15
   16:- module(drs_to_xml, [
   17		drs_to_xmlatom/2,     % +DRS, -XMLAtom
   18		drs_to_xmlterm/2      % +DRS, -XMLTerm
   19	]).

XML markup generation for Attempto DRS

This module creates an XML representation for an Attempto DRS (as generated by APE).

author
- Tobias Kuhn
version
- 2009-03-16 */
   30:- use_module(xmlterm_to_xmlatom, [
   31		xmlterm_to_xmlatom/2
   32	]).   33
   34
   35% The following operators are used in the DRS.
   36:- op(400, fx, -).   37:- op(400, fx, ~).   38:- op(500, xfx, =>).   39:- op(500, xfx, v).
 drs_to_xmlatom(+DRS, -XMLAtom) is det
Generates an XML representation (as an atom) for the DRS.
   46drs_to_xmlatom(DRS, XMLAtom) :-
   47    copy_term(DRS, DRSCopy),
   48    numbervars(DRSCopy, 0, _),
   49    drs_to_xmlterm(DRSCopy, XMLTerm),
   50    xmlterm_to_xmlatom(XMLTerm, XMLAtom).
 drs_to_xmlterm(+DRS, -XMLTerm) is det
Generates a Prolog-style XML representation (using element/3) for the DRS.
   58drs_to_xmlterm(drs(Dom, Conds), element('DRS', [domain=DomC], Content)) :-
   59    convert_vars(Dom, DomC),
   60    convert_conds(Conds, Content).
 write_nv(+Arg, +Term) is det
Writes Term onto the standard output. The variable representations '$VAR'(_) are printed as capital letters A, B, C, etc. Together with the format_predicate declaration, this allows us to use the placeholder '~v' in format/3.
   70write_nv(_, Term) :-
   71    write_term(Term, [numbervars(true), quoted(true)]).
   72
   73% '~v' in format/3 is used to pretty print variables.
   74:- format_predicate(v, write_nv(_Arg, _Term)).
 convert(+Term, -Atom) is det
Converts Term into an atom. The variable representations '$VAR'(_) are pretty printed as capital letters.
   82convert(In, Out) :-
   83    format(atom(Out), '~v', [In]).
 convert_vars(+VarList, -Atom) is det
Converts a list of variables into an atom that contains the variable names separated by blank spaces.
   91convert_vars([], '').
   92
   93% no blank space added, if there is only one variable
   94convert_vars([V], Out) :-
   95    convert(V, Out),
   96    !.
   97
   98convert_vars([V|Rest], Out) :-
   99    convert_vars(Rest, OutRest),
  100    convert(V, OutV),
  101    atom_concat(' ', OutRest, OutTemp),
  102    atom_concat(OutV, OutTemp, Out).
 convert_conds(+CondList, -XMLTerm) is det
Generates a Prolog-style XML representation for the list of conditions.
  109convert_conds([], []).
  110
  111convert_conds([Term-SentenceID/TokenID|RestIn], [element(Name, AttsC, [])|RestOut]) :-
  112    Term =.. [Name|Atts],
  113    create_attlist(Name, Atts, AttsTemp),
  114    append(AttsTemp, [sentid=SentenceID, tokid=TokenID], AttsC),
  115    convert_conds(RestIn, RestOut).
  116
  117convert_conds([- DRSIn|RestIn], [element('Negation', [], [DRSOut])|RestOut]) :-
  118    drs_to_xmlterm(DRSIn, DRSOut),
  119    convert_conds(RestIn, RestOut).
  120
  121convert_conds([~ DRSIn|RestIn], [element('NAF', [], [DRSOut])|RestOut]) :-
  122    drs_to_xmlterm(DRSIn, DRSOut),
  123    convert_conds(RestIn, RestOut).
  124
  125convert_conds([can(DRSIn)|RestIn], [element('Possibility', [], [DRSOut])|RestOut]) :-
  126    drs_to_xmlterm(DRSIn, DRSOut),
  127    convert_conds(RestIn, RestOut).
  128
  129convert_conds([must(DRSIn)|RestIn], [element('Necessity', [], [DRSOut])|RestOut]) :-
  130    drs_to_xmlterm(DRSIn, DRSOut),
  131    convert_conds(RestIn, RestOut).
  132
  133convert_conds([should(DRSIn)|RestIn], [element('Recommendation', [], [DRSOut])|RestOut]) :-
  134    drs_to_xmlterm(DRSIn, DRSOut),
  135    convert_conds(RestIn, RestOut).
  136
  137convert_conds([may(DRSIn)|RestIn], [element('Admissibility', [], [DRSOut])|RestOut]) :-
  138    drs_to_xmlterm(DRSIn, DRSOut),
  139    convert_conds(RestIn, RestOut).
  140
  141convert_conds([question(DRSIn)|RestIn], [element('Question', [], [DRSOut])|RestOut]) :-
  142    drs_to_xmlterm(DRSIn, DRSOut),
  143    convert_conds(RestIn, RestOut).
  144
  145convert_conds([command(DRSIn)|RestIn], [element('Command', [], [DRSOut])|RestOut]) :-
  146    drs_to_xmlterm(DRSIn, DRSOut),
  147    convert_conds(RestIn, RestOut).
  148
  149convert_conds([CondsIn|RestIn], [element('PredicateGroup', [], CondsOut)|RestOut]) :-
  150	is_list(CondsIn),
  151    convert_conds(CondsIn, CondsOut),
  152    convert_conds(RestIn, RestOut).
  153
  154convert_conds([DRSIn1 => DRSIn2|RestIn], [element('Implication', [], [DRSOut1,DRSOut2])|RestOut]) :-
  155    drs_to_xmlterm(DRSIn1, DRSOut1),
  156    drs_to_xmlterm(DRSIn2, DRSOut2),
  157    convert_conds(RestIn, RestOut).
  158
  159convert_conds([DRSIn1 v DRSIn2|RestIn], [element('Disjunction', [], [DRSOut1,DRSOut2])|RestOut]) :-
  160    drs_to_xmlterm(DRSIn1, DRSOut1),
  161    drs_to_xmlterm(DRSIn2, DRSOut2),
  162    convert_conds(RestIn, RestOut).
  163
  164convert_conds([V:DRSIn|RestIn], [element('Proposition', [ref=VC], [DRSOut])|RestOut]) :-
  165    convert(V, VC),
  166    drs_to_xmlterm(DRSIn, DRSOut),
  167    convert_conds(RestIn, RestOut).
 create_attlist(+PredName, +ArgList, -XMLTerm) is det
Creates a list of name/value pairs for the arguments ArgList of the predicate PredName.
  175create_attlist(modifier_pp, [X,Prep,Y], [ref=XC,prep=Prep,obj=YC]) :-
  176    convert(X, XC),
  177    convert(Y, YC).
  178
  179create_attlist(modifier_adv, [X,Adv,Deg], [ref=XC,adverb=Adv,degree=Deg]) :-
  180    convert(X, XC).
  181
  182create_attlist(object, [X,Noun,S,I,J,N], [ref=XC,noun=Noun,struct=S,unit=I,numrel=J,num=N]) :-
  183    convert(X, XC).
  184
  185create_attlist(predicate, [E,Verb,X], [ref=EC,verb=Verb,subj=XC]) :-
  186    convert(E, EC),
  187    convert(X, XC).
  188
  189create_attlist(predicate, [E,Verb,X,Y], [ref=EC,verb=Verb,subj=XC,obj=YC]) :-
  190    var_or_expr(Y),
  191    convert(E, EC),
  192    convert(X, XC),
  193    convert(Y, YC).
  194
  195create_attlist(predicate, [E,Verb,X,Y,Z], [ref=EC,verb=Verb,subj=XC,obj=YC,indobj=ZC]) :-
  196    var_or_expr(Z),
  197    convert(E, EC),
  198    convert(X, XC),
  199    convert(Y, YC),
  200    convert(Z, ZC).
  201
  202create_attlist(has_part, [X,Y], [group=XC,member=YC]) :-
  203    convert(X, XC),
  204    convert(Y, YC).
  205
  206create_attlist(property, [X,Adj,Deg], [ref=XC,adj=Adj,degree=Deg]) :-
  207    convert(X, XC).
  208
  209create_attlist(property, [X,Adj,Deg,Y], [ref=XC,adj=Adj,degree=Deg,obj=YC]) :-
  210    var_or_expr(Y),
  211    convert(X, XC),
  212    convert(Y, YC).
  213
  214create_attlist(property, [X,Adj,Y,Deg,CompTarget,Z], [ref=XC,adj=Adj,obj1=YC,degree=Deg,comptarget=CompTarget,obj2=ZC]) :-
  215    convert(X, XC),
  216    convert(Y, YC),
  217    convert(Z, ZC).
  218
  219create_attlist(query, [X,Q], [obj=XC,question=Q]) :-
  220    convert(X, XC).
  221
  222create_attlist(relation, [X,R,Y], [obj1=XC,rel=R,obj2=YC]) :-
  223    convert(X, XC),
  224    convert(Y, YC).
  225
  226create_attlist(formula, [A,O,B], [obj1=AC,op=O,obj2=BC]) :-
  227    convert(A, AC),
  228    convert(B, BC).
 var_or_expr(+Term) is det
Succeeds if the term is a (numbervared) variable or an ACE expression.
  235var_or_expr(X) :-
  236    X =.. [F,_|_],
  237    member(F, ['$VAR', string, int, real, expr, set, list, named])