1% This file is part of the Attempto Parsing Engine (APE).
    2% Copyright 2008-2010, 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(owlfss_owlrdfxml, [
   17		owlfss_owlrdfxml/2
   18	]).

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

author
- Kaarel Kaljurand
- Jean-Marc Vanel (jmv)
version
- 2010-11-01
deprecated
-
To be done
- Cover all the OWL/SWRL axioms here, not only those that the DRS->OWL/SWRL generates.
- Complete support for property chains.
- Complete support for SWRL data properties, built-ins. */
 owlfss_owlrdfxml(+Ontology:term, -RDFXML:term) is det
Arguments:
Ontology- is an OWL/SWRL ontology in Functional-Style Syntax (Prolog notation)
RDFXML- is the OWL/SWRL ontology in RDF/XML (SWI-Prolog's XML notation)
   42owlfss_owlrdfxml('Ontology'(Name, AxiomList), RDFXML) :-
   43
   44	atom_concat(Name, '#', NameHash),
   45
   46	axiomlist_rdf(AxiomList, AxiomListRdf, DescriptionList),
   47
   48	list_to_set(DescriptionList, DescriptionListSorted),
   49
   50	findall(element('rdf:Description', ['rdf:about'=About], [
   51		element('rdf:type', ['rdf:resource'=Resource], [])
   52		]
   53	), member(about(About, Resource), DescriptionListSorted), DescriptionListRdf),
   54
   55
   56	append(AxiomListRdf, DescriptionListRdf, Everything),
   57
   58	RDFXML = element('rdf:RDF', [
   59		'xml:base'=Name,
   60		xmlns=NameHash,
   61		'xmlns:owl'='http://www.w3.org/2002/07/owl#',
   62		'xmlns:owl11'='http://www.w3.org/2006/12/owl11#',
   63		'xmlns:swrl'='http://www.w3.org/2003/11/swrl#',
   64		'xmlns:swrlb'='http://www.w3.org/2003/11/swrlb#',
   65		'xmlns:rdf'='http://www.w3.org/1999/02/22-rdf-syntax-ns#',
   66		'xmlns:rdfs'='http://www.w3.org/2000/01/rdf-schema#'
   67		], [
   68		element('owl:Ontology', ['rdf:about'=''], []) | Everything
   69		]
   70	).
 axiomlist_rdf(+AxiomList:list, -XML:xml, -DescriptionList:list) is det
   76axiomlist_rdf([], [], []).
   77
   78axiomlist_rdf([Axiom | AxiomList], [AxiomRdf | AxiomListRdf], DescriptionList) :-
   79	axiom_rdf(Axiom, AxiomRdf, D1),
   80	axiomlist_rdf(AxiomList, AxiomListRdf, D2),
   81	append(D1, D2, DescriptionList).
 axiom_rdf(+Axiom:term, -Rdf:xml) is det
   86axiom_rdf('Declaration'(Individual),
   87	element('owl:Thing', IndividualRdf, []),
   88	[]
   89) :-
   90	individual_rdf(Individual, about, IndividualRdf).
   91
   92
   93axiom_rdf('ClassAssertion'(Class, Individual),
   94	element('owl:Thing', IndividualRdf, [
   95		element('rdf:type', [], [ClassRdf])
   96		]
   97	),
   98	DescriptionList
   99) :-
  100	individual_rdf(Individual, about, IndividualRdf),
  101	class_rdf(Class, ClassRdf, DescriptionList).
  102
  103
  104% @bug cleanup the NS-stuff, we assume here that NS=''
  105axiom_rdf('ObjectPropertyAssertion'('ObjectProperty'(NS:NamedProperty), Individual1, Individual2),
  106	element('owl:Thing', Individual1Rdf, [
  107		element(NamedProperty, Individual2Rdf, [])
  108		]
  109	),
  110	[about(RdfNamedProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty')]
  111) :-
  112	get_uri(NS:NamedProperty, RdfNamedProperty),
  113	individual_rdf(Individual1, about, Individual1Rdf),
  114	individual_rdf(Individual2, resource, Individual2Rdf).
  115
  116
  117% @bug cleanup the NS-stuff, we assume here that NS=''
  118axiom_rdf('DataPropertyAssertion'('DataProperty'(NS:NamedProperty), Individual, '^^'(Value, Type)),
  119	element('owl:Thing', IndividualRdf, [
  120		element(NamedProperty, ['rdf:datatype'=Type], [ValueRdf])
  121		]
  122	),
  123	[about(RdfNamedProperty, 'http://www.w3.org/2002/07/owl#DatatypeProperty')]
  124) :-
  125	get_uri(NS:NamedProperty, RdfNamedProperty),
  126	individual_rdf(Individual, about, IndividualRdf),
  127	datavalue_rdf(Value, ValueRdf).
  128
  129
  130axiom_rdf('SameIndividual'([Individual1, Individual2]),
  131	element('owl:Thing', Individual1Rdf, [
  132		element('owl:sameAs', Individual2Rdf, [])
  133		]
  134	),
  135	[]
  136) :-
  137	individual_rdf(Individual1, about, Individual1Rdf),
  138	individual_rdf(Individual2, resource, Individual2Rdf).
  139
  140
  141axiom_rdf('DifferentIndividuals'([Individual1, Individual2]),
  142	element('owl:Thing', Individual1Rdf, [
  143		element('owl:differentFrom', Individual2Rdf, [])
  144		]
  145	),
  146	[]
  147) :-
  148	individual_rdf(Individual1, about, Individual1Rdf),
  149	individual_rdf(Individual2, resource, Individual2Rdf).
  150
  151
  152axiom_rdf('SubClassOf'('Class'(owl:'Thing'), D),
  153	element('owl:Class', ['rdf:about'='http://www.w3.org/2002/07/owl#Thing'], [
  154		element('rdfs:subClassOf', [], [DRdf])
  155		]
  156	),
  157	DescriptionList
  158) :-
  159	!,
  160	class_rdf(D, DRdf, DescriptionList).
  161
  162
  163axiom_rdf('SubClassOf'('Class'(C), D),
  164	element('owl:Class', ['rdf:about'=RdfC], [
  165		element('rdfs:subClassOf', [], [DRdf])
  166		]
  167	),
  168	DescriptionList
  169) :-
  170	!,
  171	get_uri(C, RdfC),
  172	class_rdf(D, DRdf, DescriptionList).
  173
  174
  175axiom_rdf('SubClassOf'(C, D),
  176	element('owl:Class', [], [
  177		CRdf,
  178		element('rdfs:subClassOf', [], [DRdf])
  179		]
  180	),
  181	DescriptionList
  182) :-
  183	class_rdf(C, element('owl:Class', [], [CRdf]), D1),
  184	class_rdf(D, DRdf, D2),
  185	append(D1, D2, DescriptionList).
  186
  187% BUG: incomplete chain support
  188axiom_rdf('SubObjectPropertyOf'('ObjectPropertyChain'(['ObjectProperty'(SubProperty1), 'ObjectProperty'(SubProperty2)]), 'ObjectProperty'(SuperProperty)),
  189	element('rdf:Description', [], [
  190		element('rdf:type', ['rdf:resource'='http://www.w3.org/1999/02/22-rdf-syntax-ns#List'], []),
  191		element('rdfs:subPropertyOf', ['rdf:resource'=RdfSuperProperty], []),
  192		element('rdf:first', ['rdf:resource'=RdfSubProperty1], []),
  193		element('rdf:rest', ['rdf:parseType'='Collection'], [
  194			element('rdf:Description', ['rdf:about'=RdfSubProperty2], [])
  195			]
  196		)
  197		]
  198	),
  199	[
  200	about(RdfSubProperty1, 'http://www.w3.org/2002/07/owl#ObjectProperty'),
  201	about(RdfSubProperty2, 'http://www.w3.org/2002/07/owl#ObjectProperty'),
  202	about(RdfSuperProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty')
  203	]
  204) :-
  205	!,
  206	get_uri(SubProperty1, RdfSubProperty1),
  207	get_uri(SubProperty2, RdfSubProperty2),
  208	get_uri(SuperProperty, RdfSuperProperty).
  209
  210
  211axiom_rdf('SubObjectPropertyOf'('ObjectProperty'(SubProperty), 'ObjectInverseOf'('ObjectProperty'(SuperProperty))),
  212	element('owl:ObjectProperty', ['rdf:about'=RdfSubProperty], [
  213		element('rdfs:subPropertyOf', ['rdf:parseType'='Resource'], [
  214			element('rdf:type', ['rdf:resource'='http://www.w3.org/2002/07/owl#ObjectProperty'], []),
  215			element('owl:inverseOf', ['rdf:resource'=RdfSuperProperty], [])
  216			]
  217		)
  218		]
  219	),
  220	[about(RdfSuperProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty')]
  221) :-
  222	!,
  223	get_uri(SubProperty, RdfSubProperty),
  224	get_uri(SuperProperty, RdfSuperProperty).
  225
  226
  227axiom_rdf('SubObjectPropertyOf'('ObjectProperty'(SubProperty), 'ObjectProperty'(SuperProperty)),
  228	element('owl:ObjectProperty', ['rdf:about'=RdfSubProperty], [
  229		element('rdfs:subPropertyOf', ['rdf:resource'=RdfSuperProperty], [])
  230		]
  231	),
  232	[about(RdfSuperProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty')]
  233) :-
  234	get_uri(SubProperty, RdfSubProperty),
  235	get_uri(SuperProperty, RdfSuperProperty).
  236
  237
  238% BUG: inverse is transitive IFF the named property is transitive
  239axiom_rdf('TransitiveObjectProperty'('ObjectInverseOf'('ObjectProperty'(Property))),
  240	element('owl:ObjectProperty', ['rdf:about'=RdfProperty], [
  241		element('rdf:type', ['rdf:resource'='http://www.w3.org/2002/07/owl#TransitiveProperty'], [])
  242		]
  243	),
  244	[]
  245) :-
  246	get_uri(Property, RdfProperty).
  247
  248
  249axiom_rdf('TransitiveObjectProperty'('ObjectProperty'(Property)),
  250	element('owl:ObjectProperty', ['rdf:about'=RdfProperty], [
  251		element('rdf:type', ['rdf:resource'='http://www.w3.org/2002/07/owl#TransitiveProperty'], [])
  252		]
  253	),
  254	[]
  255) :-
  256	get_uri(Property, RdfProperty).
  257
  258
  259axiom_rdf('DisjointObjectProperties'(['ObjectProperty'(R), 'ObjectProperty'(S)]),
  260	element('owl:ObjectProperty', ['rdf:about'=RdfR], [
  261		element('owl11:disjointObjectProperties', ['rdf:resource'=RdfS], [])
  262		]
  263	),
  264	[about(RdfS, 'http://www.w3.org/2002/07/owl#ObjectProperty')]
  265) :-
  266	get_uri(R, RdfR),
  267	get_uri(S, RdfS).
  268
  269
  270% BUG: does not work
  271% TODO: implement also Domain and Range support
  272axiom_rdf('DisjointClasses'(['Class'(C), 'Class'(D)]),
  273	element('owl:Class', ['rdf:about'=RdfC], [
  274		element('owl:disjointWith', [], [RdfD])
  275		]
  276	),
  277	AboutList
  278) :-
  279	get_uri(C, RdfC),
  280	class_rdf(D, RdfD, AboutList).
  281
  282
  283% Finally, we can generate SWRL/RDF/XML from our own functional SWRL representation
  284axiom_rdf(
  285	'DLSafeRule'('Body'(DescriptionList1), 'Head'(DescriptionList2)),
  286	element('swrl:Imp', [], [
  287		element('swrl:body', [], AtomList1),
  288		element('swrl:head', [], AtomList2)
  289	]),
  290	AboutList
  291):-
  292	descriptionlist_atomlist(DescriptionList1, AtomList1, _, AboutList1),
  293	descriptionlist_atomlist(DescriptionList2, AtomList2, _, AboutList2),
  294	append(AboutList1, AboutList2, AboutList).
 classlist_rdf(+ClassList:list, -Rdf:term, -DescriptionList:list) is det
  300classlist_rdf([], [], []).
  301
  302classlist_rdf([Class | ClassList], [ClassRdf | RdfList], DescriptionList) :-
  303	class_rdf(Class, ClassRdf, D1),
  304	classlist_rdf(ClassList, RdfList, D2),
  305	append(D1, D2, DescriptionList).
 class_rdf(+Class:term, -Rdf:term, -DescriptionList:list) is det
  311class_rdf('Class'(owl:'Thing'),
  312	element('owl:Class', ['rdf:about'='http://www.w3.org/2002/07/owl#Thing'], []),
  313	[]
  314) :- !.
  315
  316
  317class_rdf(
  318	'ObjectIntersectionOf'(ClassList),
  319	element('owl:Class', [], [element('owl:intersectionOf', ['rdf:parseType'='Collection'], RdfList)]),
  320	DescriptionList
  321) :-
  322	classlist_rdf(ClassList, RdfList, DescriptionList).
  323
  324
  325class_rdf(
  326	'ObjectUnionOf'(ClassList),
  327	element('owl:Class', [], [element('owl:unionOf', ['rdf:parseType'='Collection'], RdfList)]),
  328	DescriptionList
  329) :-
  330	classlist_rdf(ClassList, RdfList, DescriptionList).
  331
  332
  333class_rdf(
  334	'ObjectOneOf'(IndividualList),
  335	element('owl:Class', [], [element('owl:oneOf', ['rdf:parseType'='Collection'], RdfList)]),
  336	[]
  337) :-
  338	individuallist_rdf(IndividualList, RdfList).
  339
  340
  341class_rdf(
  342	'ObjectComplementOf'(Class),
  343	element('owl:Class', [], [element('owl:complementOf', [], [ClassRdf])]),
  344	DescriptionList
  345) :-
  346	class_rdf(Class, ClassRdf, DescriptionList).
  347
  348
  349class_rdf(
  350	'ObjectSomeValuesFrom'(Property, Class),
  351	element('owl:Restriction', [], [
  352		OnPropertyRdf,
  353		element('owl:someValuesFrom', [], [ClassRdf])
  354	]),
  355	[about(NamedProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty') | DescriptionList]
  356) :-
  357	onproperty_rdf(Property, OnPropertyRdf, NamedProperty),
  358	class_rdf(Class, ClassRdf, DescriptionList).
  359
  360
  361class_rdf(
  362	'ObjectHasSelf'(Property),
  363	element('owl11:SelfRestriction', [], [OnPropertyRdf]),
  364	[about(NamedProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty')]
  365) :-
  366	onproperty_rdf(Property, OnPropertyRdf, NamedProperty).
  367
  368
  369% Note: this is added for backwards compatibility (with OWL DL) reasons
  370class_rdf(
  371	'ObjectMinCardinality'(Number, Property, 'Class'(owl:'Thing')),
  372	element('owl:Restriction', [], [
  373		OnPropertyRdf,
  374		element('owl:minCardinality', ['rdf:datatype'='http://www.w3.org/2001/XMLSchema#nonNegativeInteger'], [NumberRdf])
  375	]),
  376	[about(NamedProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty')]
  377) :-
  378	datavalue_rdf(Number, NumberRdf),
  379	onproperty_rdf(Property, OnPropertyRdf, NamedProperty).
  380
  381
  382class_rdf(
  383	'ObjectMinCardinality'(Number, Property, Class),
  384	element('owl:Restriction', [], [
  385		OnPropertyRdf,
  386		element('owl:minCardinality', ['rdf:datatype'='http://www.w3.org/2001/XMLSchema#nonNegativeInteger'], [NumberRdf]),
  387		element('owl11:onClass', [], [ClassRdf])
  388	]),
  389	[about(NamedProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty') | DescriptionList]
  390) :-
  391	datavalue_rdf(Number, NumberRdf),
  392	onproperty_rdf(Property, OnPropertyRdf, NamedProperty),
  393	class_rdf(Class, ClassRdf, DescriptionList).
  394
  395
  396% Note: this is added for backwards compatibility (with OWL DL) reasons
  397class_rdf(
  398	'ObjectMaxCardinality'(Number, Property, 'Class'(owl:'Thing')),
  399	element('owl:Restriction', [], [
  400		OnPropertyRdf,
  401		element('owl:maxCardinality', ['rdf:datatype'='http://www.w3.org/2001/XMLSchema#nonNegativeInteger'], [NumberRdf])
  402	]),
  403	[about(NamedProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty')]
  404) :-
  405	datavalue_rdf(Number, NumberRdf),
  406	onproperty_rdf(Property, OnPropertyRdf, NamedProperty).
  407
  408
  409class_rdf(
  410	'ObjectMaxCardinality'(Number, Property, Class),
  411	element('owl:Restriction', [], [
  412		OnPropertyRdf,
  413		element('owl:maxCardinality', ['rdf:datatype'='http://www.w3.org/2001/XMLSchema#nonNegativeInteger'], [NumberRdf]),
  414		element('owl11:onClass', [], [ClassRdf])
  415	]),
  416	[about(NamedProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty') | DescriptionList]
  417) :-
  418	datavalue_rdf(Number, NumberRdf),
  419	onproperty_rdf(Property, OnPropertyRdf, NamedProperty),
  420	class_rdf(Class, ClassRdf, DescriptionList).
  421
  422
  423% Note: this is added for backwards compatibility (with OWL DL) reasons
  424class_rdf(
  425	'ObjectExactCardinality'(Number, Property, 'Class'(owl:'Thing')),
  426	element('owl:Restriction', [], [
  427		OnPropertyRdf,
  428		element('owl:cardinality', ['rdf:datatype'='http://www.w3.org/2001/XMLSchema#nonNegativeInteger'], [NumberRdf])
  429	]),
  430	[about(NamedProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty')]
  431) :-
  432	datavalue_rdf(Number, NumberRdf),
  433	onproperty_rdf(Property, OnPropertyRdf, NamedProperty).
  434
  435
  436class_rdf(
  437	'ObjectExactCardinality'(Number, Property, Class),
  438	element('owl:Restriction', [], [
  439		OnPropertyRdf,
  440		element('owl:cardinality', ['rdf:datatype'='http://www.w3.org/2001/XMLSchema#nonNegativeInteger'], [NumberRdf]),
  441		element('owl11:onClass', [], [ClassRdf])
  442	]),
  443	[about(NamedProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty') | DescriptionList]
  444) :-
  445	datavalue_rdf(Number, NumberRdf),
  446	onproperty_rdf(Property, OnPropertyRdf, NamedProperty),
  447	class_rdf(Class, ClassRdf, DescriptionList).
  448
  449
  450class_rdf(
  451	'ObjectHasValue'(Property, Individual),
  452	element('owl:Restriction', [], [
  453		OnPropertyRdf,
  454		element('owl:hasValue', IndividualRdf, [])
  455	]),
  456	[about(NamedProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty')]
  457) :-
  458	onproperty_rdf(Property, OnPropertyRdf, NamedProperty),
  459	individual_rdf(Individual, resource, IndividualRdf).
  460
  461
  462class_rdf(
  463	'DataHasValue'(Property, '^^'(Value, Type)),
  464	element('owl:Restriction', [], [
  465		OnPropertyRdf,
  466		element('owl:hasValue', ['rdf:datatype'=Type], [ValueRdf])
  467	]),
  468	[about(NamedProperty, 'http://www.w3.org/2002/07/owl#DatatypeProperty')]
  469) :-
  470	onproperty_rdf(Property, OnPropertyRdf, NamedProperty),
  471	datavalue_rdf(Value, ValueRdf).
  472
  473
  474class_rdf('Class'(NamedClass), element('owl:Class', ['rdf:about'=RdfNamedClass], []), []) :-
  475	get_uri(NamedClass, RdfNamedClass).
 onproperty_rdf(+PropertyExpression:term, -RdfXml:term, -NamedProperty:atom) is semidet
Note: data properties cannot have inverses
  483onproperty_rdf('ObjectInverseOf'('ObjectProperty'(NamedProperty)),
  484	element('owl:onProperty', ['rdf:parseType'='Resource'], [
  485		element('rdf:type', ['rdf:resource'='http://www.w3.org/2002/07/owl#ObjectProperty'], []),
  486		element('owl:inverseOf', ['rdf:resource'=RdfNamedProperty], [])
  487		]
  488	),
  489	RdfNamedProperty
  490) :-
  491	!,
  492	get_uri(NamedProperty, RdfNamedProperty).
  493
  494onproperty_rdf('ObjectProperty'(NamedProperty), element('owl:onProperty', ['rdf:resource'=RdfNamedProperty], []), RdfNamedProperty) :-
  495	get_uri(NamedProperty, RdfNamedProperty).
  496
  497onproperty_rdf('DataProperty'(NamedProperty), element('owl:onProperty', ['rdf:resource'=RdfNamedProperty], []), RdfNamedProperty) :-
  498	get_uri(NamedProperty, RdfNamedProperty).
 individuallist_rdf(+IndividualList:list, -Rdf:term) is det
  504individuallist_rdf([], []).
  505
  506individuallist_rdf([Individual | IndividualList], [element('owl:Thing', RdfNamedIndividual, []) | RdfList]) :-
  507	individual_rdf(Individual, about, RdfNamedIndividual),
  508	individuallist_rdf(IndividualList, RdfList).
 individual_rdf(+Individual:term, +Type:atom, -Rdf:term) is det
  515% @deprecated
  516individual_rdf('AnonymousIndividual'('$VAR'(Number)), _, ['rdf:nodeID'=AnonymousIndividual]) :-
  517	!,
  518	concat_atom(['Ind', Number], AnonymousIndividual).
  519
  520individual_rdf('AnonymousIndividual'(Number), _, ['rdf:nodeID'=AnonymousIndividual]) :-
  521	concat_atom(['Ind', Number], AnonymousIndividual).
  522
  523individual_rdf('NamedIndividual'(Individual), about, ['rdf:about'=NamedIndividual]) :-
  524	get_uri(Individual, NamedIndividual).
  525
  526individual_rdf('NamedIndividual'(Individual), resource, ['rdf:resource'=NamedIndividual]) :-
  527	get_uri(Individual, NamedIndividual).
 descriptionlist_atomlist(+DescriptionList:list, -AtomList:list) is det
  533descriptionlist_atomlist([], [], ['rdf:resource'='http://www.w3.org/1999/02/22-rdf-syntax-ns#nil'], []).
  534
  535descriptionlist_atomlist(
  536	[Description | DescriptionList],
  537	[
  538		element('swrl:AtomList', [], [
  539			element('rdf:first', [], [Atom]),
  540			element('rdf:rest', AttrList, AtomList)
  541			]
  542		)
  543	],
  544	[],
  545	AboutList
  546) :-
  547	description_atom(Description, Atom, AboutList1),
  548	descriptionlist_atomlist(DescriptionList, AtomList, AttrList, AboutList2),
  549	append(AboutList1, AboutList2, AboutList).
 description_atom(+Description:term, -Atom:term, -AboutList:list) is det
To be done
- data properties, built-ins
  556description_atom(
  557	'ClassAtom'('Class'(Class), Argument),
  558	element('swrl:ClassAtom', [], [
  559		element('swrl:argument1', ['rdf:resource'=RdfArgument], []),
  560		element('swrl:classPredicate', ['rdf:resource'=RdfClass], [])
  561	]),
  562	[about(RdfClass, 'http://www.w3.org/2002/07/owl#Class') | AboutList]
  563) :-
  564	!,
  565	get_uri(Class, RdfClass),
  566	argument_rdf(Argument, RdfArgument, AboutList).
  567
  568description_atom(
  569	'ObjectPropertyAtom'('ObjectProperty'(Property), Argument1, Argument2),
  570	element('swrl:IndividualPropertyAtom', [], [
  571		element('swrl:argument1', ['rdf:resource'=RdfArgument1], []),
  572		element('swrl:argument2', ['rdf:resource'=RdfArgument2], []),
  573		element('swrl:propertyPredicate', ['rdf:resource'=RdfProperty], [])
  574	]),
  575	[about(RdfProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty') | AboutList]
  576) :-
  577	!,
  578	get_uri(Property, RdfProperty),
  579	argument_rdf(Argument1, RdfArgument1, AboutList1),
  580	argument_rdf(Argument2, RdfArgument2, AboutList2),
  581	append(AboutList1, AboutList2, AboutList).
  582
  583% jmv
  584description_atom(
  585	'DataPropertyAtom'('DataProperty'(Property), Argument1, Argument2),
  586	element('swrl:IndividualPropertyAtom', [], [
  587		element('swrl:argument1', ['rdf:resource'=RdfArgument1], []),
  588		% TODO: case when Argument2 is an expression; maybe create an expression with =
  589		element('swrl:argument2', ['rdf:resource'=RdfArgument2], []),
  590		element('swrl:propertyPredicate', ['rdf:resource'=RdfProperty], [])
  591	]),
  592	[about(RdfProperty, 'http://www.w3.org/2002/07/owl#ObjectProperty') | AboutList]
  593) :-
  594	!,
  595	get_uri(Property, RdfProperty),
  596	argument_rdf(Argument1, RdfArgument1, AboutList1),
  597	argument_rdf(Argument2, RdfArgument2, AboutList2),
  598	append(AboutList1, AboutList2, AboutList).
  599
  600description_atom(
  601	'SameIndividualAtom'(Argument1, Argument2),
  602	element('swrl:SameIndividualAtom', [], [
  603		element('swrl:argument1', ['rdf:resource'=RdfArgument1], []),
  604		element('swrl:argument2', ['rdf:resource'=RdfArgument2], [])
  605	]),
  606	AboutList
  607) :-
  608	!,
  609	argument_rdf(Argument1, RdfArgument1, AboutList1),
  610	argument_rdf(Argument2, RdfArgument2, AboutList2),
  611	append(AboutList1, AboutList2, AboutList).
  612
  613description_atom(
  614	'DifferentIndividualsAtom'(Argument1, Argument2),
  615	element('swrl:DifferentIndividualsAtom', [], [
  616		element('swrl:argument1', ['rdf:resource'=RdfArgument1], []),
  617		element('swrl:argument2', ['rdf:resource'=RdfArgument2], [])
  618	]),
  619	AboutList
  620) :-
  621	!,
  622	argument_rdf(Argument1, RdfArgument1, AboutList1),
  623	argument_rdf(Argument2, RdfArgument2, AboutList2),
  624	append(AboutList1, AboutList2, AboutList).
  625
  626description_atom(
  627	'ClassAtom'(ComplexClass, Argument),
  628	element('swrl:ClassAtom', [], [
  629		element('swrl:argument1', ['rdf:resource'=RdfArgument], []),
  630		element('swrl:classPredicate', [], [ComplexClassRdf])
  631	]),
  632	AboutList
  633) :-
  634	class_rdf(ComplexClass, ComplexClassRdf, AboutList1),
  635	argument_rdf(Argument, RdfArgument, AboutList2),
  636	append(AboutList1, AboutList2, AboutList).
  637
  638description_atom(
  639	builtIn(Op, X1, X2),
  640	element('swrl:BuiltinAtom', [], [
  641		element('swrl:builtin', ['rdf:resource'=SWRL_OP], []),
  642		element('swrl:arguments', [], [
  643			element('rdf:Description', [], [
  644				element('rdf:first', ['rdf:resource'=RdfArgument1], []),
  645				element('rdf:rest', [], [
  646					element('rdf:Description', [], [
  647						element('rdf:first', ['rdf:resource'=RdfArgument2], []),
  648						element('rdf:rest', ['rdf:resource'='http://www.w3.org/1999/02/22-rdf-syntax-ns#nil'], [])
  649					])
  650				])
  651			])
  652		])
  653	]),
  654	AboutList
  655) :-
  656	concat_atom(['http://www.w3.org/2003/11/swrlb#', Op], SWRL_OP),
  657	argument_rdf(X1, RdfArgument1, AboutList1),
  658	argument_rdf(X2, RdfArgument2, AboutList2),
  659	append([AboutList1, AboutList2], AboutList).
  660
  661
  662% added by jmv
  663description_atom(
  664	builtIn(Op, X1, X2, X3),
  665	element('swrl:BuiltinAtom', [], [
  666		element('swrl:builtin', ['rdf:resource'=SWRL_OP], []),
  667		element('swrl:arguments', [], [
  668			element('rdf:Description', [], [
  669				element('rdf:first', ['rdf:resource'=RdfArgument1], []),
  670				element('rdf:rest', [], [
  671					element('rdf:Description', [], [
  672						element('rdf:first', ['rdf:resource'=RdfArgument2], []),
  673						element('rdf:rest', [], [
  674							element('rdf:Description', [], [
  675								element('rdf:first', ['rdf:resource'=RdfArgument3], []),
  676								element('rdf:rest', ['rdf:resource'='http://www.w3.org/1999/02/22-rdf-syntax-ns#nil'], [])
  677							])
  678						])
  679					])
  680				])
  681			])
  682		])
  683	]),
  684	AboutList
  685) :-
  686	concat_atom(['http://www.w3.org/2003/11/swrlb#', Op], SWRL_OP),
  687	argument_rdf(X1, RdfArgument1, AboutList1),
  688	argument_rdf(X2, RdfArgument2, AboutList2),
  689	argument_rdf(X3, RdfArgument3, AboutList3),
  690	append([AboutList1, AboutList2, AboutList3], AboutList).
 argument_rdf(+VarOrInd:term, -VarOrIndName:atom, -About:list) is det
deprecated
-
  697argument_rdf('Variable'('$VAR'(Variable)), RdfVariable, [about(RdfVariable, 'http://www.w3.org/2003/11/swrl#Variable')]) :-
  698	!,
  699	concat_atom(['#x', Variable], RdfVariable).
  700
  701argument_rdf('Variable'(Variable), RdfVariable, [about(RdfVariable, 'http://www.w3.org/2003/11/swrl#Variable')]) :-
  702	concat_atom(['#x', Variable], RdfVariable).
  703
  704argument_rdf('NamedIndividual'(Individual), RdfIndividual, []) :-
  705	get_uri(Individual, RdfIndividual).
 datavalue_rdf(+Value:number, -ValueRdf:atom) is det
Converts a number into an atom.
  712datavalue_rdf(Value, ValueRdf) :-
  713	number(Value),
  714	!,
  715	atom_number(ValueRdf, Value).
  716
  717datavalue_rdf(Value, Value).
 get_uri(+Name:term, -RdfName:atom) is det
bug
- we assume that 'owl' always means 'http://www.w3.org/2002/07/owl', etc.
  724get_uri(':'(owl, 'Thing'), 'http://www.w3.org/2002/07/owl#Thing') :-
  725	!.
  726
  727get_uri(':'(ace, 'Universe'), 'http://attempto.ifi.uzh.ch/ace#Universe') :-
  728	!.
  729
  730get_uri(':'(ace, 'contain'), 'http://attempto.ifi.uzh.ch/ace#contain') :-
  731	!.
  732
  733get_uri(':'(NS, C), RdfC) :-
  734	concat_atom([NS, '#', C], RdfC)