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(owlswrl_to_xml, [
   17		owlswrl_to_xml/2
   18	]).   19
   20:- use_module(owlswrl_iri, [
   21		iri_to_prefix/2
   22	]).

OWL/SWRL Functional-Style Syntax to OWL/SWRL XML converter

author
- Kaarel Kaljurand
version
- 2013-02-06
bug
- support for datatype properties is not implemented or buggy
To be done
- anonymous individuals should not be turned into regular individuals

% It would be good to output also AnonymousIndividual, but this needs more work, % e.g. "There is a woman that every man likes." is rejected by the OWL-API OWLXMLParser: % Element not found: Expected at least one individual in object oneOf % Note sure why this is not allowed...

- Use abbreviated IRIs and prefix declarations, no need for atom concat
- Cover all of OWL/SWRL not just the constructs that ACE->OWL/SWRL generates

*/

 owlswrl_to_xml(+OWL:term, -XML:term) is det
Arguments:
OWL- is OWL ontology in Functional-Style Syntax (Prolog notation)
XML- is OWL ontology in XML (SWI-Prolog's XML notation)
   50owlswrl_to_xml(
   51	'Ontology'(OntologyIri, AxiomList),
   52	element('Ontology', [
   53		'xml:base' = 'http://www.w3.org/2002/07/owl#',
   54		'xmlns' = 'http://www.w3.org/2002/07/owl#',
   55		'ontologyIRI' = OntologyIri
   56		], ElList)
   57	) :-
   58	iri_to_prefix(OntologyIri, Prefix),
   59	axiomlist_to_xml(AxiomList, Prefix, ElList).
 axiomlist_to_xml(+Axioms:list, Prefix:atom, -TermList:list) is det
Converts a list of OWL/SWRL axioms in Prolog notation into a list of XML elements in Prolog notation.
Arguments:
Axioms- is a list of Prolog terms (representing OWL/SWRL axioms)
Prefix- IRI that is used in case of the default namespace as a prefix
ElementList- is a list of XML elements
   71axiomlist_to_xml([], _, []).
   72
   73axiomlist_to_xml([Axiom | Axioms], Prefix, [element(ElName, [], Children) | ElList]) :-
   74	axiom_to_xml(Axiom, Prefix, ElName, Children),
   75	!,
   76	axiomlist_to_xml(Axioms, Prefix, ElList).
 axiom_to_xml(+Axiom:term, +Prefix:atom, -ElName:atom, -Children:list) is det
Axiom
   83axiom_to_xml('SubClassOf'(CE1, CE2), Prefix, 'SubClassOf', [CE1x, CE2x]) :-
   84	!,
   85	ce_to_xml(CE1, Prefix, CE1x),
   86	ce_to_xml(CE2, Prefix, CE2x).
   87
   88axiom_to_xml('ClassAssertion'(CE, I), Prefix, 'ClassAssertion', [CEx, Ix]) :-
   89	!,
   90	ce_to_xml(CE, Prefix, CEx),
   91	ie_to_xml(I, Prefix, Ix).
   92
   93axiom_to_xml('ObjectPropertyAssertion'(OPE, I1, I2), Prefix, 'ObjectPropertyAssertion', [OPEx, I1x, I2x]) :-
   94	!,
   95	ope_to_xml(OPE, Prefix, OPEx),
   96	ie_to_xml(I1, Prefix, I1x),
   97	ie_to_xml(I2, Prefix, I2x).
   98
   99axiom_to_xml('DataPropertyAssertion'(DPE, I, L), Prefix, 'DataPropertyAssertion', [DPEx, Ix, Lx]) :-
  100	!,
  101	dpe_to_xml(DPE, Prefix, DPEx),
  102	ie_to_xml(I, Prefix, Ix),
  103	l_to_xml(L, Lx).
  104
  105axiom_to_xml('SubObjectPropertyOf'('ObjectPropertyChain'(E_list), OPE), Prefix, 'SubObjectPropertyOf', [element('ObjectPropertyChain', [], Ex_list), OPEx]) :-
  106	!,
  107	elist_to_xml(ope, E_list, Prefix, Ex_list),
  108	ope_to_xml(OPE, Prefix, OPEx).
  109
  110axiom_to_xml('SubObjectPropertyOf'(OPE1, OPE2), Prefix, 'SubObjectPropertyOf', [OPE1x, OPE2x]) :-
  111	!,
  112	ope_to_xml(OPE1, Prefix, OPE1x),
  113	ope_to_xml(OPE2, Prefix, OPE2x).
  114
  115axiom_to_xml('TransitiveObjectProperty'(OPE), Prefix, 'TransitiveObjectProperty', [OPEx]) :-
  116	!,
  117	ope_to_xml(OPE, Prefix, OPEx).
  118
  119axiom_to_xml('ObjectPropertyDomain'(OPE, CE), Prefix, 'ObjectPropertyDomain', [OPEx, CEx]) :-
  120	!,
  121	ope_to_xml(OPE, Prefix, OPEx),
  122	ce_to_xml(CE, Prefix, CEx).
  123
  124axiom_to_xml('ObjectPropertyRange'(OPE, CE), Prefix, 'ObjectPropertyRange', [OPEx, CEx]) :-
  125	!,
  126	ope_to_xml(OPE, Prefix, OPEx),
  127	ce_to_xml(CE, Prefix, CEx).
  128
  129axiom_to_xml('DLSafeRule'('Body'(Atom_list1), 'Head'(Atom_list2)), Prefix, 'DLSafeRule', Ex_list) :-
  130	!,
  131	elist_to_xml(a, Atom_list1, Prefix, Atomx_list1),
  132	elist_to_xml(a, Atom_list2, Prefix, Atomx_list2),
  133	Ex_list = [
  134		element('Body', [], Atomx_list1),
  135		element('Head', [], Atomx_list2)
  136	].
  137
  138axiom_to_xml(Axiom, Prefix, Name, List_x) :-
  139	axiom_is_owl_list(Axiom, Type, Name, List),
  140	!,
  141	elist_to_xml(Type, List, Prefix, List_x).
  142
  143axiom_to_xml(IllegalArg, _, _, _) :-
  144	throw(error('Not an axiom', context(axiom_to_xml/3, IllegalArg))).
Arguments:
Type- is one of {ce, ope, ie, ...}
  152axiom_is_owl_list('DisjointClasses'(List), ce, 'DisjointClasses', List).
  153axiom_is_owl_list('DisjointObjectProperties'(List), ope, 'DisjointObjectProperties', List).
  154axiom_is_owl_list('SameIndividual'(List), ie, 'SameIndividual', List).
  155axiom_is_owl_list('DifferentIndividuals'(List), ie, 'DifferentIndividuals', List).
  156
  157ce_is_owl_list('ObjectIntersectionOf'(List), ce, 'ObjectIntersectionOf', List).
  158ce_is_owl_list('ObjectUnionOf'(List), ce, 'ObjectUnionOf', List).
  159ce_is_owl_list('ObjectOneOf'(List), ie, 'ObjectOneOf', List).
List of OWL/SWRL expressions
  166elist_to_xml(_Type, [], _Prefix, []).
  167
  168elist_to_xml(Type, [CE | Tail], Prefix, [CEx | Tailx]) :-
  169	e_to_xml(Type, CE, Prefix, CEx),
  170	elist_to_xml(Type, Tail, Prefix, Tailx).
  174e_to_xml(ce, E, Prefix, Ex) :- ce_to_xml(E, Prefix, Ex).
  175e_to_xml(ope, E, Prefix, Ex) :- ope_to_xml(E, Prefix, Ex).
  176e_to_xml(dpe, E, Prefix, Ex) :- dpe_to_xml(E, Prefix, Ex).
  177e_to_xml(ie, E, Prefix, Ex) :- ie_to_xml(E, Prefix, Ex).
  178e_to_xml(a, E, Prefix, Ex) :- a_to_xml(E, Prefix, Ex).
  179e_to_xml(v_or_l, E, Prefix, Ex) :- v_or_l_to_xml(E, Prefix, Ex).
Class Expression
  186ce_to_xml(CE, Prefix, Xml) :-
  187	ce_is_owl_list(CE, Type, Name, List),
  188	!,
  189	elist_to_xml(Type, List, Prefix, List_x),
  190	get_xml(Name, List_x, Xml).
  191
  192ce_to_xml('ObjectComplementOf'(CE), Prefix, Xml) :-
  193	!,
  194	ce_to_xml(CE, Prefix, CEx),
  195	get_xml('ObjectComplementOf', [CEx], Xml).
  196
  197ce_to_xml('ObjectHasSelf'(OPE), Prefix, Xml) :-
  198	!,
  199	ope_to_xml(OPE, Prefix, OPEx),
  200	get_xml('ObjectHasSelf', [OPEx], Xml).
  201
  202ce_to_xml('DataHasValue'(DPE, L), Prefix, Xml) :-
  203	!,
  204	dpe_to_xml(DPE, Prefix, DPEx),
  205	l_to_xml(L, Lx),
  206	get_xml('DataHasValue', [DPEx, Lx], Xml).
  207
  208ce_to_xml('ObjectSomeValuesFrom'(OPE, CE), Prefix, Xml) :-
  209	!,
  210	ope_to_xml(OPE, Prefix, OPEx),
  211	ce_to_xml(CE, Prefix, CEx),
  212	get_xml('ObjectSomeValuesFrom', [OPEx, CEx], Xml).
  213
  214ce_to_xml('ObjectMinCardinality'(N, OPE, CE), Prefix, Xml) :-
  215	!,
  216	number(N),
  217	ope_to_xml(OPE, Prefix, OPEx),
  218	ce_to_xml(CE, Prefix, CEx),
  219	get_xml('ObjectMinCardinality', [cardinality = N], [OPEx, CEx], Xml).
  220
  221ce_to_xml('ObjectMaxCardinality'(N, OPE, CE), Prefix, Xml) :-
  222	!,
  223	number(N),
  224	ope_to_xml(OPE, Prefix, OPEx),
  225	ce_to_xml(CE, Prefix, CEx),
  226	get_xml('ObjectMaxCardinality', [cardinality = N], [OPEx, CEx], Xml).
  227
  228ce_to_xml('ObjectExactCardinality'(N, OPE, CE), Prefix, Xml) :-
  229	!,
  230	number(N),
  231	ope_to_xml(OPE, Prefix, OPEx),
  232	ce_to_xml(CE, Prefix, CEx),
  233	get_xml('ObjectExactCardinality', [cardinality = N], [OPEx, CEx], Xml).
  234
  235ce_to_xml(EntityRef, Prefix, Xml) :-
  236	entity_to_xml('Class', EntityRef, Prefix, Xml),
  237	!.
  238
  239ce_to_xml(IllegalArg, _, _) :-
  240	throw(error('Not a class expression', context(ce_to_xml/3, IllegalArg))).
 ope_to_xml(EntityRef, Prefix, Xml)
Object Property Expression
  247ope_to_xml('ObjectInverseOf'(OPE), Prefix, Xml) :-
  248	ope_to_xml(OPE, Prefix, OPEx),
  249	get_xml('ObjectInverseOf', [OPEx], Xml).
  250
  251ope_to_xml(EntityRef, Prefix, Xml) :-
  252	entity_to_xml('ObjectProperty', EntityRef, Prefix, Xml),
  253	!.
  254
  255ope_to_xml(IllegalArg, _, _) :-
  256	throw(error('Not an object property expression', context(ope_to_xml/3, IllegalArg))).
 dpe_to_xml(EntityRef, Prefix, Xml)
Data Property Expression
  263dpe_to_xml(EntityRef, Prefix, Xml) :-
  264	entity_to_xml('DataProperty', EntityRef, Prefix, Xml),
  265	!.
  266
  267dpe_to_xml(IllegalArg, _, _) :-
  268	throw(error('Not a data property expression', context(dpe_to_xml/3, IllegalArg))).
 ie_to_xml(EntityRef, Prefix, Xml)
Individual Expression (i.e. named or anonymous individual)

BUG: anonymous individuals are currently converted into named individuals. In order to ouput them as anonymous, use instead: ie_to_xml(nodeID(Name), _, element('AnonymousIndividual', ['nodeID' = Name], [])).

  279ie_to_xml('nodeID'(NodeId), Prefix, Xml) :-
  280	!,
  281	atom_concat('Ind', NodeId, IName),
  282	entity_to_xml('NamedIndividual', '':IName, Prefix, Xml).
  283
  284ie_to_xml(EntityRef, Prefix, Xml) :-
  285	entity_to_xml('NamedIndividual', EntityRef, Prefix, Xml),
  286	!.
  287
  288ie_to_xml(IllegalArg, _, _) :-
  289	throw(error('Not an individual', context(ie_to_xml/3, IllegalArg))).
 a_to_xml(+Atom, +Prefix, -Xml)
SWRL Atoms
  296a_to_xml('ClassAtom'(CE, IArg), Prefix, Xml) :-
  297	ce_to_xml(CE, Prefix, CEx),
  298	v_or_ie_to_xml(IArg, Prefix, IArgx),
  299	get_xml('ClassAtom', [CEx, IArgx], Xml).
  300
  301% a_to_xml('DataRangeAtom'(...), Prefix, Xml).
  302
  303a_to_xml('ObjectPropertyAtom'(OPE, IArg1, IArg2), Prefix, Xml) :-
  304	ope_to_xml(OPE, Prefix, OPEx),
  305	v_or_ie_to_xml(IArg1, Prefix, IArg1x),
  306	v_or_ie_to_xml(IArg2, Prefix, IArg2x),
  307	get_xml('ObjectPropertyAtom', [OPEx, IArg1x, IArg2x], Xml).
  308
  309a_to_xml('DataPropertyAtom'(DPE, IArg, DArg), Prefix, Xml) :-
  310	dpe_to_xml(DPE, Prefix, DPEx),
  311	v_or_ie_to_xml(IArg, Prefix, IArgx),
  312	v_or_l_to_xml(DArg, Prefix, DArgx),
  313	get_xml('DataPropertyAtom', [DPEx, IArgx, DArgx], Xml).
  314
  315a_to_xml('BuiltInAtom'(Op, DArgList), Prefix, element('BuiltInAtom', ['IRI' = Iri], DArgList_x)) :-
  316	get_iri(Op, Prefix, Iri),
  317	elist_to_xml(v_or_l, DArgList, Prefix, DArgList_x).
  318
  319a_to_xml('SameIndividualAtom'(IArg1, IArg2), Prefix, Xml) :-
  320	v_or_ie_to_xml(IArg1, Prefix, IArg1x),
  321	v_or_ie_to_xml(IArg2, Prefix, IArg2x),
  322	get_xml('SameIndividualAtom', [IArg1x, IArg2x], Xml).
  323
  324a_to_xml('DifferentIndividualsAtom'(IArg1, IArg2), Prefix, Xml) :-
  325	v_or_ie_to_xml(IArg1, Prefix, IArg1x),
  326	v_or_ie_to_xml(IArg2, Prefix, IArg2x),
  327	get_xml('DifferentIndividualsAtom', [IArg1x, IArg2x], Xml).
  328
  329a_to_xml(IllegalArg, _, _) :-
  330	throw(error('Not a SWRL atom', context(a_to_xml/3, IllegalArg))).
 v_or_l_to_xml(+Variable_or_Literal, +Prefix, -Xml)
Literal or SWRL Variable
  337v_or_l_to_xml(Literal, _Prefix, Ex) :-
  338	catch(l_to_xml(Literal, Ex), _, fail),
  339	!.
  340
  341v_or_l_to_xml(Variable, Prefix, Ex) :-
  342	catch(v_to_xml(Variable, Prefix, Ex), _, fail),
  343	!.
  344
  345v_or_l_to_xml(IllegalArg, _, _) :-
  346	throw(error('Not a variable nor a literal', context(v_or_l_to_xml/3, IllegalArg))).
 v_or_ie_to_xml(+Individual_or_Variable, +Prefix, -Xml)
Individual or SWRL Variable
  353v_or_ie_to_xml(Individual, Prefix, Ex) :-
  354	catch(ie_to_xml(Individual, Prefix, Ex), _, fail),
  355	!.
  356
  357v_or_ie_to_xml(Variable, Prefix, Ex) :-
  358	catch(v_to_xml(Variable, Prefix, Ex), _, fail),
  359	!.
  360
  361v_or_ie_to_xml(IllegalArg, _, _) :-
  362	throw(error('Not an individual nor a SWRL variable', context(v_or_ie_to_xml/3, IllegalArg))).
 l_to_xml
Literal
  369l_to_xml('^^'(Data, Datatype), element('Literal', ['datatypeIRI' = Datatype], [PCDATA])) :-
  370	!,
  371	datatype_pcdata_data(PCDATA, Datatype, Data).
 v_to_xml(+Variable:term, +Prefix:atom, -VariableX:term)
SWRL Variable
  378v_to_xml('Variable'(Iri), _, element('Variable', ['IRI' = Iri], [])).
  383entity_to_xml(Type, Name, Prefix, element(Type, ['IRI' = Iri], [])) :-
  384	get_iri(Name, Prefix, Iri).
Builds the SWI-Prolog's XML-term given the XML element name, the attributes, and child elements.
  393get_xml(El, Els, element(El, [], Els)).
  394get_xml(El, Attrs, Els, element(El, Attrs, Els)).
 get_iri(+Name:term, +Prefix:atom, -Iri:atom) is det
If Name is an atom then considers it an IRI and returns it as it is. Otherwise expects that Name has the form ':'(NS,LocalName) and uses the default prefix, namespace abbreviation and the local name to create the IRI.
  404get_iri(Iri, _, Iri) :-
  405	atom(Iri).
  406
  407get_iri(owl:'Thing', _, 'http://www.w3.org/2002/07/owl#Thing').
  408get_iri(owl:'Nothing', _, 'http://www.w3.org/2002/07/owl#Nothing').
  409
  410get_iri(ace:'Universe', _, 'http://attempto.ifi.uzh.ch/ace#Universe').
  411get_iri(ace:'contain', _, 'http://attempto.ifi.uzh.ch/ace#contain').
  412
  413get_iri('':Name, DefaultPrefix, Iri) :-
  414	atom_concat(DefaultPrefix, Name, Iri).
  415
  416get_iri(NS:Name, _, Iri) :-
  417	prefix_map(NS, Prefix),
  418	atom_concat(Prefix, Name, Iri).
 prefix_map(?PrefixName:atom, ?Prefix:atom)
  424prefix_map(owl, 'http://www.w3.org/2002/07/owl#').
  425prefix_map(ace, 'http://attempto.ifi.uzh.ch/ace#').
  426prefix_map(swrlb, 'http://www.w3.org/2003/11/swrlb#').
 datatype_pcdata_data(+PCDATA:atom, +Datatype:atom, -Data:atomic) is det
The purpose of this rule is to convert some of the PCDATA into Prolog numbers. In case of failure, the PCDATA is returned as it is, i.e. it will be represented as an atom.

Note that if the PCDATA (i.e. an atom) cannot be converted into a number then atom_number/2 throws an exception. This is caught at higher level (for the time being).

Arguments:
PCDATA- is a data value (atom)
Datatype- is an XML Schema datatype
Data- is a data value (atom or number)
  443datatype_pcdata_data(PCDATA, Datatype, Data) :-
  444	is_numbertype(Datatype),
  445	!,
  446	atom_number(PCDATA, Data).
  447
  448datatype_pcdata_data(PCDATA, _, PCDATA).
 is_numbertype(+Datatype:atom) is det
Arguments:
Datatype- is an XML Schema datatype
  455is_numbertype('http://www.w3.org/2001/XMLSchema#int').
  456is_numbertype('http://www.w3.org/2001/XMLSchema#integer').
  457is_numbertype('http://www.w3.org/2001/XMLSchema#nonNegativeInteger').
  458is_numbertype('http://www.w3.org/2001/XMLSchema#float').
  459is_numbertype('http://www.w3.org/2001/XMLSchema#double').
  460is_numbertype('http://www.w3.org/2001/XMLSchema#short').
  461is_numbertype('http://www.w3.org/2001/XMLSchema#long')