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:- module(owlswrl_to_fss, [
   16		owlswrl_to_fss/1,
   17		owlswrl_to_fss/2
   18	]).   19
   20:- use_module(owlswrl_iri, [
   21		iri_to_prefix/2,
   22		builtin_iri/2
   23	]).

OWL/SWRL serializer into OWL/SWRL Functional-Style Syntax

author
- Kaarel Kaljurand
version
- 2013-06-03
To be done
- Escaping
- Test on the regression test set if OWL-API can load the output produced here

*/

Writes the OWL/SWRL ontology in Functional-Style Syntax into the current stream.
   42owlswrl_to_fss('Ontology'(OntologyIri, Axioms)) :-
   43	iri_to_prefix(OntologyIri, Prefix),
   44	format("Prefix(:=<~w>)~n", [Prefix]),
   45	forall(
   46		builtin_iri(Abbr, IriPrefix),
   47		format("Prefix(~w:=<~w>)~n", [Abbr, IriPrefix])
   48	),
   49	format("Ontology(<~w>~n", [OntologyIri]),
   50	print_list(Axioms, 1),
   51	format(")~n").
   52
   53%
   54owlswrl_to_fss(Ontology, OntologyFss) :-
   55	with_output_to(atom(OntologyFss), owlswrl_to_fss(Ontology)).
 print_compound
   61print_compound(OwlFss, Level) :-
   62	OwlFss =.. [Name | Args],
   63	PrettyIndent is Level * 3,
   64	writef('%r%w(\n', [' ', PrettyIndent, Name]),
   65	NewLevel is Level + 1,
   66	print_list(Args, NewLevel),
   67	writef('%r)\n', [' ', PrettyIndent]).
 print_list
Don't change the order, e.g. an empty list should not be "mistaken" for an atom.
   75print_list([], _).
   76
   77print_list([Head | Tail], Level) :-
   78	is_list(Head),
   79	!,
   80	print_list(Head, Level),
   81	print_list(Tail, Level).
   82
   83print_list([Expression | Tail], Level) :-
   84	print_terminal(Expression, Level),
   85	!,
   86	print_list(Tail, Level).
   87
   88print_list([Head | Tail], Level) :-
   89	compound(Head),
   90	!,
   91	print_compound(Head, Level),
   92	print_list(Tail, Level).
 print_terminal
   98print_terminal(Number, Level) :-
   99	number(Number),
  100	!,
  101	PrettyIndent is Level * 3,
  102	writef('%r%w\n', [' ', PrettyIndent, Number]).
  103
  104print_terminal(Iri, Level) :-
  105	atom(Iri),
  106	!,
  107	PrettyIndent is Level * 3,
  108	writef('%r<%w>\n', [' ', PrettyIndent, Iri]).
  109
  110print_terminal('Variable'(Iri), Level) :-
  111	PrettyIndent is Level * 3,
  112	writef('%rVariable(<%w>)\n', [' ', PrettyIndent, Iri]).
  113
  114print_terminal('BuiltInAtom'(Iri, DArgList), Level) :-
  115	PrettyIndent is Level * 3,
  116	writef('%rBuiltInAtom(<%w>\n', [' ', PrettyIndent, Iri]),
  117	NewLevel is Level + 1,
  118	print_list(DArgList, NewLevel),
  119	writef('%r)\n', [' ', PrettyIndent]).
  120
  121print_terminal('^^'(DataValue, DataType), Level) :-
  122	PrettyIndent is Level * 3,
  123	writef('%r"%w"^^<%w>\n', [' ', PrettyIndent, DataValue, DataType]).
  124
  125print_terminal(Terminal, Level) :-
  126	pretty_print(Terminal, PrettyExpression),
  127	!,
  128	PrettyIndent is Level * 3,
  129	writef('%r%w\n', [' ', PrettyIndent, PrettyExpression]).
  130
  131
  132pretty_print(nodeID(Number), '_':Number).
  133pretty_print(NS:Name, NS:Name)