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_ruleml, [ 17 drs_to_ruleml/2 18 ]).
38% The following operators are used in the DRS. 39:- op(400, fx, -). 40:- op(500, xfx, =>). 41:- op(500, xfx, v).
49drs_to_ruleml(
50 DRS,
51 element('RuleML', [], [
52 element('Assert', [], Elements)
53 ])
54 ) :-
55 existdrs_els(DRS, Elements).
62conds_and(Conds, ElementsOut) :- 63 conds_elements(Conds, Elements), 64 conds_and_x(Elements, ElementsOut). 65 66conds_and_x([Element], Element) :- 67 !. 68 69conds_and_x(Elements, element('And', [], Elements)).
76conds_elements([], []). 77 78conds_elements([Cond | Tail], [SCond | STail]) :- 79 cond_element(Cond, SCond), 80 conds_elements(Tail, STail).
As the structure of the DRS doesn't match exactly to the structure of the RuleML element (as specified by Hirtle), we have to do some ugly appending.
91cond_element(drs(Dom1, Conds1) => DRS2, 92 element('Forall', [], SubElements0) 93 ) :- 94 args_els(Dom1, VarElements1), 95 conds_and(Conds1, Element1), 96 existdrs_els(DRS2, SubElements2), 97 append([Element1], SubElements2, SubElements1), 98 append(VarElements1, [element('Implies', [], SubElements1)], SubElements0). 99 100 101cond_element(DRS1 v DRS2, 102 element('Or', [], SubElements0) 103 ) :- 104 existdrs_els(DRS1, SubElements1), 105 existdrs_els(DRS2, SubElements2), 106 append(SubElements1, SubElements2, SubElements0). 107 108 109cond_element(-DRS, element('Neg', [], SubElements)) :- 110 existdrs_els(DRS, SubElements). 111 112 113cond_element(Conds, Element) :- 114 is_list(Conds), 115 conds_and(Conds, Element). 116 117 118cond_element(Condition-_, element('Atom', [], [element('Rel', [], [Functor]) | Els])) :- 119 Condition =.. [Functor | Args], 120 args_els(Args, Els).
Note that all terms (e.g. variables and numbers) must be converted into atoms to be compatible with the way how SWI represents XML documents internally.
131args_els([], []). 132 133args_els([H | T], [element('Var', [], [HH]) | ElsTail]) :- 134 var(H), 135 !, 136 term_to_atom(H, HH), 137 args_els(T, ElsTail). 138 139args_els([H | T], [element('Data', [], [HH]) | ElsTail]) :- 140 number(H), 141 !, 142 term_to_atom(H, HH), % alternatively: atom_number(HH, H) 143 args_els(T, ElsTail). 144 145args_els([H | T], [element('Ind', [], [H]) | ElsTail]) :- 146 args_els(T, ElsTail).
153existdrs_els(drs([],Conds), [Element]) :- 154 !, 155 conds_and(Conds, Element). 156 157existdrs_els(drs(Dom,Conds), [element('Exists', [], Elements)]) :- 158 args_els(Dom, DomElements), 159 conds_and(Conds, Element), 160 append(DomElements, [Element], Elements).
173to_xml([], ''). 174 175to_xml([element(Name, _, Elements) | T], Xml) :- 176 to_xml(Elements, ElXml), 177 to_xml(T, TXml), 178 format(atom(Xml), '<~w>~w</~w>~n~w', [Name, ElXml, Name, TXml]). 179 180to_xml([Text | T], Xml) :- 181 atom(Text), 182 to_xml(T, TXml), 183 format(atom(Xml), '~w~w', [Text, TXml])
Attempto DRS to RuleML/folog converter
This module converts the Attempto DRS into RuleML/folog as specified by David Hirtle in his thesis.