RDF package

This commit is contained in:
Vitor Santos Costa 2010-07-28 11:34:41 +01:00
parent 7b9ab9252c
commit 8d3b9ad16c
102 changed files with 7067 additions and 1 deletions

280
packages/RDF/ChangeLog Normal file
View File

@ -0,0 +1,280 @@
[Sep 10 2009]
* MODIFIED: Dropped support for old RDF Bag/Alt/Seq syntax.
* ENHANCED: Speedup processing of xml: properties in RDF/XML parser.
* ENHANCED: Compile-time expansion of the term-rewriter that is used by
the RDF/XML parser.
[Aug 20 2009]
* FIXED: Support for \U in rdf_ntriples.pl (used to parse W3C test results)
[Jul 30 2009]
* CLEANUP: Modernise rdf.pl and rdf_db.pl module handling.
[Jul 2 2009]
* FIXED: handle rdf:datatype earlier (compliant to the revised RDF syntax
specs). This fixes empty strings using
<rdfs:label rdf:datatype="&xsd;string"/>
Spotted by Chris Mungall
[Jun 22 2009]
* FIXED: avoid bnodes in types nodes for rdf_write_xml/2.
[Jun 9 2009]
* FIXED: RDF typed-nodes (<ns:Class ...>...</ns:Class> descriptions) if the expansion of ns contains %-escaped characters. Jochem Liem.
[Mar 19 2009]
* CLEANUP: Removed all trailing whitespace from all source-files. This avoids many GIT (merge) warnings.
[Mar 12 2009]
* MODIFIED: Renamed concat_atom/2,3 into atomic_list_concat/2,3 for compatibility. Moved the old predicates into library(backcomp). It is adviced to update your code, but 99% of the code will remain working because the old definitions are autoloaded.
[Mar 6 2009]
* FIXED: rdf_write_xml with different encodings. Patch by Keri Harris.
[Jan 21 2009]
* FIXED: RDF writer: write valid XML if the namespace entity contains characters
that must be %-escaped. Jacopo Urbani.
[Jan 13 2009]
* FIXED: RDF/XML could save illegal XML if multiple namespaces are used
for predicates where one namespace is a prefix of another one. Jacopo Urbani.
[Dec 19 2008]
* ADDED: Pass content_length through process_rdf/3
[Sep 11 2008]
* PORT: Add AC_PREREQ to configure.h for systems that auto-select autoconf
versions. After tip by Ulrich Neumerkel.
[Aug 11 2008]
* INSTALL: Remove all configure files from the git repository
[Apr 18 2008]
* MODIFIED: Renamed hash_term/2 to term_hash/2. Added hash_term/2 to
library(backcomp), so most code should not notice this.
[Feb 28 2008]
* FIXED: rdf_write_xml/2 loops if it encounters an rdf:Bag.
[Feb 18 2008]
* FIXED: More fixes for proper handling of rdf:Bag
[Feb 13 2008]
* FIXED: Emit rdf:Bag attributes (etc.) as rdf:li
* FIXED: possible failure in rdf_write_xml with http://t-d-b.org?
[Jan 14 2008]
* FIXED: Bug#343: Handling bnodes in rdf_write_xml. Yver Raimond.
* FIXED: Added support for rdf:NodeID to rdf_write_xml/2. Yves Raimond.
[Dec 13 2007]
* FIXED: library(rdf_write) to deal with operators. Related to Bug#332
Oct 29, 2007
* FIXED: extract namespaces used in typed literals. Yves Raimond.
Jul 9, 2007
* FIXED: xml:lang with empty literals. Jochem Liem.
Jun 14, 2007
* FIXED: return rdf:parseType="Literal" as literal of type
rdf:XMLLiteral.
Jan 18, 2007
* ADDED: embedded(Bool) option to process_rdf/3
Jun 25, 2006
* CLEANUP: Delete unused global variable.
Jun 5, 2006
* FIXED: use UTF-8 decoder from new library(utf8). Our own internal one
was broken.
Apr 25, 2006
* FIXED: decoding of unicode-URIs using UTF-8 over %XX%XX.
Apr 13, 2006
* ADDED: library rdf_write to write an RDF file from a list of triples.
Dec 8, 2005
* FIXED: xmlns attributes in descriptions. Bijan Parsia
Nov 23, 2005
* ADDED: option db(DB) to parse_rdf/2.
Nov 10, 2005
* COMMENT: Comment use of IRI
Jul 7, 2005
* ADDED: Pass entity(Name, Value) to XML parser
Jul 5, 2005
* FIXED: Perform proper URI decoding to Unicode atoms
Jul 4, 2005
* FIXED: Make "make check" work from the build directory.
Mar 31, 2005
* FIXED: memory leak in process_rdf/2
Mar 29, 2005
* FIXED: dataType --> datatype (Vangelis Vassiliadis)
Oct 21, 2004
* FIXED: Bug#196: avoid need for autoloading. Sandro Hawke.
Sep 13, 2004
* ADDED: namespaces(-NameSpaces) option to load_rdf/3 and process_rdf/3
to query the document namespace declarations.
Aug 13, 2004
* MODIFIED: load_rdf/3 no longer returns resources as Prefix:URI, but
instead returns the plain atoms.
Jul 31, 2004
* ADDED: converted rdf_nt.pl into public rdf_ntriples.pl library for
loading data in the W3C ntriple format.
Jun 29, 2004
* FIXED: sharing code for blank nodes. Broken in recent cleanup.
Jun 17, 2004
* CLEANUP: start/end of loading a file, use option/3 from library
Apr 21, 2004
* ADDED: Support for xml:lang and rdf:dataType attributes.
* INTERNAL: Use global variables rather than assert/retract for
keeping track of the state for process_rdf/3.
Nov 29, 2003
* ADDED: warning for incorrect and multiple definitions of rdf:ID.
Maarten Menken.
Nov 7, 2003
* ADDED: process_rdf/3: allow processing from a stream
Oct 6, 2003
* MODIFIED: synopsis of process_rdf/3 to
process_rdf(+File, :OnTriples, +Options) for consistency and to allow
extending the option list. Old calls are mapped to the new.
* Added option blank_nodes(share) to load_rdf/3 and process_rdf/3.
Aug 18, 2003
* Guarantee that anonymous ids start with __
Mar 20, 2003
* Fixed exception in cleanup. Dominique de Waleffe.
Feb 28, 2003
* ADDED: Use BaseURI to create non-conflicting anonymous resources.
* FIXED: rdf_parser:global_id to ignore xml:base for absolute URIs
Jan 17, 2003
* FIXED: online.pl (web frontend) to avoid using goal/1 option for the
xml parser. Now uses 4.0.8 clib memfile library primitives.
* FIXED: process_rdf/3, Peter Marks.
* ADDED: parseType="Collection", satisfying the W3C Working Draft
8 November 2002.
################################################################
# Sumary of incompatibilities:
#
# Many problems in nested bag handling, changing output of
# suite/t5.rdf
#
# Content of Alt-container was incorrectly rendered as rdf:li
# instead of rdf:_1, rdf:_2, etc (suite/t27.rdf).
################################################################
* ADDED: Translate rdf:li predicates into _1, _2, etc.
* FIXED: parseType=Literal to avoid extraneous [..] around the value
Oct 28, 2002
* CLEANUP: pass base-uri as attribute, preparing for xml:base and making
the parser ready for multi-threading.
Sep 16, 2002
* MODIFIED: Allow for unqualified attribute-names
* ADDED: "make check"
Older entries
* FIXED: Type-exception in atom_chars/2
* FIXED: handling mixed <name>literal</name> and <name>object</name>
(space canonisation problem).
* CGI Demo: report errors generated before a fatal exception.
* FIXED: handling of propertyElt of the form
rdf:ID="myid" rdf:parseType="Resource"
* For objects, map NameSpace:Local to the simple concatenation of the two.
This implies:
# Subjects are always atoms
# Predicates are NameSpace:LocalName or simply Name
# Objects are atoms (URI) or literal(Value)
* Warn on things that cannot be converted into an RDF-object rather then
failing silently.
* Removed some undesirable choice-points.

129
packages/RDF/Makefile.in Normal file
View File

@ -0,0 +1,129 @@
################################################################
# SWI-Prolog `RDF' package
# Author: Jan Wielemaker. jan@swi.psy.uva.nl
# Copyright: LGPL (see COPYING or www.gnu.org
################################################################
.SUFFIXES: .tex .dvi .doc .pl
SHELL=@SHELL@
ifeq (@PROLOG_SYSTEM@,yap)
prefix = @prefix@
exec_prefix = @exec_prefix@
ROOTDIR = $(prefix)
EROOTDIR = @exec_prefix@
srcdir=@srcdir@
BINDIR = $(EROOTDIR)/bin
LIBDIR=@libdir@
YAPLIBDIR=@libdir@/Yap
SHAREDIR=$(EROOTDIR)/share/Yap
PL=@INSTALL_ENV@ $(DESTDIR)$(BINDIR)/yap $(DESTDIR)$(YAPLIBDIR)/startup.yss
LN_S=@LN_S@
EXDIR=$(LIBDIR)/examples/plunit
INSTALLDIR=$(SHAREDIR)
else # SWI
srcdir=.
PLBASE=@PLBASE@
PLARCH=@PLARCH@
PL=@PL@
XPCEBASE=$(PLBASE)/xpce
PKGDOC=$(PLBASE)/doc/packages
PCEHOME=../xpce
LIBDIR=$(PLBASE)/library
INSTALLDIR=$(LIBDIR)
endif
DOCTOTEX=$(PCEHOME)/bin/doc2tex
PLTOTEX=$(PCEHOME)/bin/pl2tex
RUNTEX=../../man/runtex
LATEX=latex
DOC=rdf2pl
TEX=$(DOC).tex
DVI=$(DOC).dvi
PDF=$(DOC).pdf
HTML=$(DOC).html
INSTALL=@INSTALL@
INSTALL_PROGRAM=@INSTALL_PROGRAM@
INSTALL_DATA=@INSTALL_DATA@
LIBPL= $(srcdir)/rdf.pl $(srcdir)/rdf_parser.pl $(srcdir)/rdf_triple.pl $(srcdir)/rewrite.pl \
$(srcdir)/rdf_ntriples.pl $(srcdir)/rdf_write.pl
XPCEPL= $(srcdir)/rdf_diagram.pl
all:
@echo "Nothing to do for this package"
install: $(LIBPL) xpce-install
$(INSTALL_DATA) $(LIBPL) $(DESTDIR)$(INSTALLDIR)
$(PL) -f none -g make -t halt
ln-install::
@$(MAKE) INSTALL_DATA=../ln-install install
xpce-install: $(XPCEPL)
if [ -d $(DESTDIR)$(XPCEBASE) ]; then \
$(INSTALL) -m 644 $(XPCEPL) $(DESTDIR)$(XPCEBASE)/prolog/lib; \
fi
rpm-install: install
pdf-install::
-$(INSTALL_DATA) $(DOC).pdf $(DESTDIR)$(PKGDOC)
html-install::
-$(INSTALL_DATA) $(DOC).html $(DESTDIR)$(PKGDOC)
uninstall:
(cd $(PLBASE)/library && rm -f $(LIBPL))
$(PL) -f none -g make -t halt
check::
$(PL) -q -f $(srcdir)/test_rdf.pl -g true -t test_rdf
$(PL) -q -f $(srcdir)/test_write.pl -g true -t test_write
################################################################
# Documentation
################################################################
doc: $(PDF) $(HTML)
pdf: $(PDF)
html: $(HTML)
$(HTML): $(TEX)
latex2html $(DOC)
mv html/index.html $@
$(PDF): $(TEX)
$(RUNTEX) --pdf $(DOC)
$(TEX): $(DOCTOTEX)
.doc.tex:
$(DOCTOTEX) $*.doc > $*.tex
.pl.tex:
$(PLTOTEX) $*.pl > $*.tex
################################################################
# Clean
################################################################
clean:
rm -f *~ *% config.log
distclean: clean
rm -f $(TARGETS) config.h config.cache config.status Makefile
rm -f $(TEX)
$(RUNTEX) --clean $(DOC)

51
packages/RDF/Makefile.mak Normal file
View File

@ -0,0 +1,51 @@
################################################################
# Build the SWI-Prolog RDF package for MS-Windows
# NOTE: This package requires the SGML package
#
# Author: Jan Wielemaker
#
# Use:
# nmake /f Makefile.mak
# nmake /f Makefile.mak install
################################################################
PLHOME=..\..
!include $(PLHOME)\src\rules.mk
all:
!IF "$(CFG)" == "rt"
install::
!ELSE
install::
copy rdf.pl "$(PLBASE)\library"
copy rdf_parser.pl "$(PLBASE)\library"
copy rdf_triple.pl "$(PLBASE)\library"
copy rewrite.pl "$(PLBASE)\library"
copy rdf_ntriples.pl "$(PLBASE)\library"
copy rdf_write.pl "$(PLBASE)\library"
$(MAKEINDEX)
!ENDIF
xpce-install::
copy rdf_diagram.pl "$(PLBASE)\xpce\prolog\lib"
$(MAKEINDEX)
html-install::
copy rdf2pl.html "$(PKGDOC)"
uninstall::
del "$(PLBASE)\library\rdf.pl"
del "$(PLBASE)\library\rdf_parser.pl"
del "$(PLBASE)\library\rdf_triple.pl"
del "$(PLBASE)\library\rewrite.pl"
del "$(PLBASE)\library\rdf_ntriples.pl"
del "$(PLBASE)\library\rdf_write.pl"
$(MAKEINDEX)
clean::
if exist *~ del *~
distclean: clean

12
packages/RDF/README Normal file
View File

@ -0,0 +1,12 @@
---+ RDF/XML parser and writer
This directory implements the RDF/XML parser on top of the SWI-Prolog
XML parser. The main entry point is provided by load_rdf/3 or the
call-back version process_rdf/3.
In addition, rdf_write.pl provides writing (serialization) of an RDD/XML
document from a list of triples.
* [[load_rdf/3]]
* [[process_rdf/3]]
* [[rdf_write_xml/2]]

19
packages/RDF/config.h.in Normal file
View File

@ -0,0 +1,19 @@
/* config.h.in. Generated from configure.in by autoheader. */
/* Define to the address where bug reports for this package should be sent. */
#undef PACKAGE_BUGREPORT
/* Define to the full name of this package. */
#undef PACKAGE_NAME
/* Define to the full name and version of this package. */
#undef PACKAGE_STRING
/* Define to the one symbol short name of this package. */
#undef PACKAGE_TARNAME
/* Define to the home page for this package. */
#undef PACKAGE_URL
/* Define to the version of this package. */
#undef PACKAGE_VERSION

View File

@ -0,0 +1,9 @@
dnl Process this file with autoconf to produce a configure script.
AC_INIT(install-sh)
AC_PREREQ([2.50])
AC_CONFIG_HEADER(config.h)
m4_include([../ac_swi_noc.m4])
AC_OUTPUT(Makefile)

457
packages/RDF/online.pl Normal file
View File

@ -0,0 +1,457 @@
/* $Id$
Part of SWI-Prolog RDF parser
Author: Jan Wielemaker
E-mail: jan@swi.psy.uva.nl
WWW: http://www.swi.psy.uva.nl/projects/SWI-Prolog/
Copying: LGPL-2. See the file COPYING or http://www.gnu.org
Copyright (C) 1990-2000 SWI, University of Amsterdam. All rights reserved.
*/
:- use_module(library(cgi)).
:- use_module(library(sgml)).
:- use_module(rdf).
:- use_module(rdf_parser).
:- use_module(rewrite).
:- use_module(pretty_print).
term_expansion(F, T) :- rew_term_expansion(F, T).
goal_expansion(F, T) :- rew_goal_expansion(F, T).
:- dynamic new_rdf_namespace/1.
parse(Text, RDFTerm, Triples) :-
parse_atom(Text, Term),
( find_rdf(Term, RDFTerm)
-> true
; RDFTerm = Term
),
xml_to_rdf(RDFTerm, [], Triples).
find_rdf(Term, RDFTerm) :-
RDFTerm = element(NS:'RDF', _, _),
term_member(RDFTerm, Term), !,
( rdf_name_space(NS)
-> true
; assert(rdf_parser:rdf_name_space(NS)),
assert(new_rdf_namespace(NS))
).
term_member(X, X).
term_member(X, Compound) :-
compound(Compound),
arg(_, Compound, Arg),
term_member(X, Arg).
% parse_atom(+Atom, -Term, +Options
%
% Parse and atom into a structured term
parse_atom(Atom, Term) :-
atom_to_memory_file(Atom, MemFile),
open_memory_file(MemFile, read, Stream),
new_sgml_parser(Parser, []),
set_sgml_parser(Parser, dialect(xmlns)),
set_sgml_parser(Parser, space(sgml)),
sgml_parse(Parser,
[ source(Stream),
document(Term)
]),
free_sgml_parser(Parser),
close(Stream),
free_memory_file(MemFile).
/*******************************
* HTML GENERATION *
*******************************/
:- op(100, fx, #).
:- op(110, xfx, ::).
emit([]) :- !.
emit([H|T]) :- !,
emit(H),
emit(T).
emit(Fmt-Args) :- !,
format(Fmt, Args),
retractall(nl_done(_)).
emit(#Term) :- !,
#Term.
emit(#Term::Content) :- !,
#Term::Content.
emit(Atom) :-
write(Atom),
retractall(nl_done(_)).
#Term::Content :-
Term =.. [Name|Attributes],
layout(before(open, Name)),
format('<~w', [Name]),
attlist(Attributes),
format('>', []),
retractall(nl_done(_)),
layout(after(open, Name)),
emit(Content),
end_tag(Name).
#pre(Text) :- !,
sgml_quote(Text, Quoted),
#pre::Quoted.
#box(Text) :- !,
box(Text, '#e0e0e0').
#box(Text, Colour) :- !,
box(Text, Colour).
#Term :-
Term =.. [Name|Attributes],
layout(before(open, Name)),
format('<~w', [Name]),
attlist(Attributes),
format('>', []),
retractall(nl_done(_)),
layout(after(open, Name)),
end_tag(Name).
end_tag(Name) :-
blines(Name, _, o), !.
end_tag(Name) :-
layout(before(close, Name)),
format('</~w>', [Name]),
retractall(nl_done(_)),
layout(after(close, Name)).
layout(before(open, Name)) :-
blines(Name, N-_, _), !,
nls(N).
layout(after(open, Name)) :-
blines(Name, _-N, _), !,
nls(N).
layout(before(close, Name)) :-
blines(Name, _, N-_), !,
nls(N).
layout(after(close, Name)) :-
blines(Name, _, _-N), !,
nls(N).
layout(_) :-
retractall(nl_done(_)).
:- dynamic
nl_done/1.
nls(N) :-
( nl_done(Done)
-> true
; Done = 0
),
ToDo is N - Done,
New is max(N, Done),
retractall(nl_done(Done)),
assert(nl_done(New)),
do_nl(ToDo).
do_nl(N) :-
N > 0, !,
nl,
NN is N - 1,
do_nl(NN).
do_nl(_).
blines(tr, 1-0, 0-0).
blines(table, 2-1, 1-1).
blines(form, 2-1, 1-1).
blines(h1, 2-0, 0-1).
blines(h2, 2-0, 0-2).
blines(h3, 2-0, 0-2).
blines(h4, 2-0, 0-2).
blines(p, 2-1, o). % omitted end-tag
attlist([]).
attlist([Name=Value|T]) :- !,
sgml_quote_value(Value, Quoted),
format(' ~w=~w', [Name, Quoted]),
attlist(T).
attlist([Name|T]) :-
format(' ~w', [Name]),
attlist(T).
head(Title) :-
emit([ 'Content-type: text/html\n\n',
'<html>\n',
'<head>\n',
'<title>~w</title>~n'-[Title],
'</head>\n\n',
'<body bgcolor="white">\n'
]).
foot :-
emit([ '</body>\n',
'</html>\n'
]).
pre(Text) :-
sgml_quote(Text, Quoted),
#pre::Quoted.
box(Text, Colour) :-
emit('<p>\n'),
#table(width='80%', align=center, border=6, bgcolor=Colour)::
[#tr::[#td(nowrap)::[#pre(Text)]]].
/*******************************
* QUOTING *
*******************************/
sgml_quote_value(Value, Arg) :-
atom_chars(Value, Chars),
( name_chars(Chars)
-> Arg = Value
; sgml_quote_chars(Chars, Quoted),
atom_chars(Arg, Quoted)
).
name_chars([H|T]) :-
char_type(H, alpha),
all_alnum(T).
all_alnum([]).
all_alnum([H|T]) :-
char_type(H, csymf),
all_alnum(T).
sgml_quote_chars(L, ['"'|T]) :-
sgml_quote2(L, T, ['"']).
sgml_quote2([], T, T).
sgml_quote2([H|T0], List, Rest) :-
sgml_quote_char(H, List, T), !,
sgml_quote2(T0, T, Rest).
sgml_quote2([H|T0], [H|T], Rest) :-
sgml_quote2(T0, T, Rest).
sgml_quote_char('<', [&, l, t, ;|T], T).
sgml_quote_char('>', [&, g, t, ;|T], T).
sgml_quote_char('&', [&, a, m, p, ;|T], T).
sgml_quote_char('"', [&, q, u, o, t, ;|T], T).
%sgml_quote_char('\'', [&, a, p, o, s, ;|T], T).
sgml_quote(Text, Quoted) :-
atom_chars(Text, Chars),
sgml_quote2(Chars, QuotedChars, []),
atom_chars(Quoted, QuotedChars).
/*******************************
* PAGE GENERATION *
*******************************/
parsed(Time, Triples) :-
length(Triples, Len),
#h2::'RDF statement parsed successfully',
#p::[ 'Your RDF statement has been parsed in ~2f seconds, '-[Time],
'creating ', #b::Len, ' triples. ',
'Please find the created triples in the table below.'
],
( getenv('HTTP_REFERER', Referer)
-> #p::[ 'If you want to try another RDF statement, please go ',
'back to ', #a(href=Referer)::'the request form', '.'
]
; true
).
rdf_table(Triples) :-
maplist(triple_row, Triples, TripleRows),
#p,
#table(caption='RDF triples',
align=center, border=2, cellpadding=3)::
[ #tr::[#th::'Subject', #th::'Predicate', #th::'Object']
| TripleRows
].
triple_row(rdf(Subj, Pred, Obj), #tr::[#td::S,#td::P,#td::O]) :-
cell(Subj, S),
cell(Pred, P),
cell(Obj, O).
cell(rdf:Local, [#em::rdf, :, #b::Local]) :- !.
cell(literal(X), [#b::'literal(', X, #b::')']) :- !.
cell(each(X), [#b::'each(', X, #b::')']) :- !.
cell(pefix(X), [#b::'prefix(', X, #b::')']) :- !.
cell(NS:Local, [NS, :, #b::Local]) :- !.
cell(V, [T]) :-
sformat(T, '~p', [V]).
/*******************************
* ERRORS *
*******************************/
show_errors :-
getenv('ERROR_FILE', File),
size_file(File, Size),
Size > 0, !,
read_file(File, Data),
#h4::[#font(color=red)::
'The following errors occurred while processing your request'],
#p,
#box(Data, '#ff8c00').
show_errors.
show_new_namepace :-
new_rdf_namespace(NS), !,
#h4::[#font(color=red)::'Warning: unofficial RDF Namespace'],
#p::['It appears your RDF description uses the unofficial ',
'name space ', #b::NS, '. ',
'This name space has been added for RDF.'
].
show_new_namepace.
/*******************************
* COMMENT *
*******************************/
comment(TextId) :-
#h4::'<hr>Comment',
#p::[ 'If you do not agree with the output or have other comments, ',
'Please write them in the text-area below and submit them'
],
getenv('REQUEST_URI', Script),
#form(method=post, action=Script)::
[ #input(type=hidden, name=id, value=TextId),
#table(align=center)::
[ #tr::[#td::[#textarea(name=comment, cols=64, rows=10)]],
#tr::[#td(align=right)::['E-mail: ', #input(name=mail)]],
#tr::[#td(align=right)::[#input(type=submit)]]
]
].
/*******************************
* REQUEST *
*******************************/
request_location('Online-requests').
% Save the request and return a local identifier for it.
save_request(Text, Id) :-
request_dir(Dir, Date),
atomic_list_concat([Dir, /, Date], DateDir),
ensure_dir(DateDir),
between(1, 10000, N),
atomic_list_concat([DateDir, /, N, '.rdf'], File),
\+ exists_file(File), !,
open(File, write, Fd),
format(Fd, '~w~n', [Text]),
close(Fd),
atomic_list_concat([Date, /, N], Id).
request_dir(BaseDir, Date) :-
get_time(Time),
convert_time(Time, Y, M, D, _, _, _, _),
request_location(BaseDir),
atomic_list_concat([D, -, M, -, Y], Date).
ensure_dir(Dir) :-
exists_directory(Dir), !.
ensure_dir(Dir) :-
make_directory(Dir).
save_comment(Id, Mail, Comment) :-
request_location(Base),
atomic_list_concat([Base, '/', Id], FileBase),
absolute_file_name(FileBase, AbsFileBase),
absolute_file_name(Base, AbsBase),
sub_atom(AbsFileBase, 0, _, _, AbsBase), % verify in tree
atom_concat(AbsFileBase, '.cmt', CmtFile),
open(CmtFile, write, Fd),
format(Fd, 'E-mail: ~w~n~n~w~n', [Mail, Comment]),
close(Fd).
/*******************************
* ENTRY *
*******************************/
main :-
cgi_get_form(Arguments),
( ( memberchk(attachment(Text), Arguments),
Text \== ''
; memberchk(rdf(Text), Arguments)
)
-> save_request(Text, TextId),
( OldTime is cputime,
parse(Text, _Prolog, Triples),
Time is cputime - OldTime
-> head('RDF Triples'),
parsed(Time, Triples),
show_errors,
show_new_namepace,
rdf_table(Triples),
comment(TextId),
foot
; head('Failed to parse'),
#p::[ 'I failed to parse your request' ],
show_errors,
comment(TextId),
foot
),
halt
; memberchk(comment(Comment), Arguments),
memberchk(id(Id), Arguments),
memberchk(mail(Mail), Arguments)
-> save_comment(Id, Mail, Comment),
head('Thanks for comment'),
#p::'Thank you for your comments',
foot,
halt
).
main :-
head('Failed'),
#p::[ 'This CGI-script failed to understand your request' ],
foot,
halt.
go :-
catch(main, E, error(E)).
error(E) :-
message_to_string(E, Msg),
head('Failed to parse'),
show_errors,
#p::[ 'An exception was raised while parsing your request:' ],
#pre(Msg),
foot,
halt.
/*******************************
* TEST *
*******************************/
test :-
read_file('suite/t1.rdf', Text),
catch(parse(Text, _Prolog, Triples), E, error(E)),
head('RDF Triples'),
rdf_table(Triples),
foot.
/*******************************
* UTIL *
*******************************/
read_file(File, Atom) :-
open(File, read, Fd),
get_code(Fd, C),
read_stream(C, Fd, Chars),
close(Fd),
atom_codes(Atom, Chars).
read_stream(-1, _, []) :- !.
read_stream(C0, Fd, [C0|T]) :-
get_code(Fd, C),
read_stream(C, Fd, T).

View File

@ -0,0 +1,167 @@
/* $Id$
Part of SWI-Prolog SGML/XML parser
Author: Jan Wielemaker
E-mail: jan@swi.psy.uva.nl
WWW: http://www.swi.psy.uva.nl/projects/SWI-Prolog/
Copying: LGPL-2. See the file COPYING or http://www.gnu.org
Copyright (C) 1990-2000 SWI, University of Amsterdam. All rights reserved.
*/
:- module(dia_pretty_print,
[ pretty_print/1
]).
:- require([ atom_length/2
, between/3
, forall/2
, is_list/1
, member/2
, memberchk/2
]).
pretty_print(Term) :-
numbervars(Term, 0, _),
pp(Term, 0),
write('.'), nl, fail.
pretty_print(_).
pp(Term, _Indent) :-
atomic(Term), !,
writeq(Term).
pp(Var, _Indent) :-
var(Var), !,
write(Var).
pp(Var, _Indent) :-
Var = '$VAR'(_), !,
print(Var).
pp('$aref'(Name), _Indent) :- !,
write(Name).
pp(Module:Term, Indent) :-
atomic(Module), !,
writeq(Module), write(:),
pp(Term, Indent).
pp([A1 = V1|ArgList], Indent) :- % [] is done by `atomic'!
is_list(ArgList),
forall(member(A, ArgList), A = (_ = _)),
longest_attribute([A1 = V1|ArgList], 0, L), !,
NewIndent is Indent + 2,
( L > 9, Indent < 25, length(ArgList, Args), Args > 1
-> ArgIndent is Indent + 4,
ValGoal = (nl, indent(ArgIndent))
; ArgIndent is Indent + 6 + L,
ValGoal = write(' ')
),
write('[ '),
pp(A1, Indent), term_length(A1, L1),
tab(L-L1), write(' ='), ValGoal,
pp(V1, ArgIndent),
forall(member(A = V, ArgList),
(write(','), nl,
indent(NewIndent),
pp(A, Indent), term_length(A, LA), tab(L-LA),
write(' ='), ValGoal, pp(V, ArgIndent))),
nl,
indent(Indent),
write(']').
pp([H|T], Indent) :-
is_list(T), !,
write('[ '),
NewIndent is Indent + 2,
pp(H, NewIndent),
forall(member(E, T),
(write(','), nl,
indent(NewIndent),
pp(E, NewIndent))),
nl,
indent(Indent),
write(']').
pp(Term, Indent) :-
functor(Term, Name, 2),
current_op(_, Type, Name),
memberchk(Type, [xfx, yfx]), !,
arg(1, Term, A1),
arg(2, Term, A2),
pp(A1, Indent), format(' ~q ', [Name]), pp(A2, Indent).
pp(Term, Indent) :-
functor(Term, Name, _Arity),
atom_length(Name, L),
NewIndent is Indent + L + 1,
format('~q(', Name),
( term_argument_length(Term, AL),
NewIndent + AL < 72
-> Wrap = nowrap
; Wrap = wrap
),
forall(generate_arg(I, Term, Arg),
pparg(I, Arg, Wrap, NewIndent)),
write(')').
generate_arg(ArgN, Term, Arg) :-
functor(Term, _, Arity),
between(1, Arity, ArgN),
arg(ArgN, Term, Arg).
pparg(1, Term, _, Indent) :- !,
pp(Term, Indent).
pparg(_, Term, wrap, Indent) :- !,
write(','), nl,
indent(Indent),
pp(Term, Indent).
pparg(_, Term, _, Indent) :-
write(', '),
pp(Term, Indent).
longest_attribute([], L, L).
longest_attribute([A = _|T], L0, L) :-
term_length(A, AL),
max(L0, AL, L1),
longest_attribute(T, L1, L).
term_length(A, AL) :-
atomic(A), !,
atom_length(A, AL).
term_length(Var, AL) :-
var(Var), !,
AL = 1.
term_length('$VAR'(N), AL) :-
varname(N, L),
length(L, AL).
term_length('$aref'(N), AL) :-
atom_length(N, AL).
term_argument_length(Term, L) :-
term_argument_length(Term, 1, 0, L).
term_argument_length(Term, A, L0, L) :-
arg(A, Term, Arg), !,
term_length(Arg, AL),
L1 is AL + L0,
NA is A + 1,
term_argument_length(Term, NA, L1, L).
term_argument_length(_, _, L, L).
max(A, B, M) :-
( A >= B
-> M = A
; M = B
).
varname(N, [C]) :-
N < 26, !,
C is N + 0'A.
varname(N, [C1, C2]) :-
C1 is N // 26 + 0'A,
C2 is N mod 26 + 0'A.
indent(I) :-
Tabs is I // 8,
forall(between(1, Tabs, _), put(9)),
Spaces is I mod 8,
tab(Spaces).

413
packages/RDF/rdf.pl Normal file
View File

@ -0,0 +1,413 @@
/* $Id$
Part of SWI-Prolog
Author: Jan Wielemaker
E-mail: wielemak@science.uva.nl
WWW: http://www.swi-prolog.org
Copyright (C): 2002-2007, University of Amsterdam
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
as published by the Free Software Foundation; either version 2
of the License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
As a special exception, if you link this library with other files,
compiled with a Free Software compiler, to produce an executable, this
library does not by itself cause the resulting executable to be covered
by the GNU General Public License. This exception does not however
invalidate any other reasons why the executable file might be covered by
the GNU General Public License.
*/
:- module(rdf,
[ load_rdf/2, % +File, -Triples
load_rdf/3, % +File, -Triples, :Options
xml_to_rdf/3, % +XML, -Triples, +Options
process_rdf/3 % +File, :OnTriples, :Options
]).
:- meta_predicate
load_rdf(+, -, :),
process_rdf(+, :, :).
:- use_module(library(sgml)). % Basic XML loading
:- use_module(library(option)). % option/3
:- use_module(library(lists)).
:- use_module(rdf_parser). % Basic parser
:- use_module(rdf_triple). % Generate triples
%% load_rdf(+File, -Triples) is det.
%% load_rdf(+File, -Triples, :Options) is det.
%
% Parse an XML file holding an RDF term into a list of RDF triples.
% see rdf_triple.pl for a definition of the output format. Options:
%
% * base_uri(+URI)
% URI to use as base
%
% * expand_foreach(+Bool)
% Apply each(Container, Pred, Object) on the members of
% Container
%
% * namespaces(-Namespaces:list(NS=URL))
% Return list of namespaces declared using xmlns:NS=URL in
% the document. This can be used to update the namespace
% list with rdf_register_ns/2.
%
% @see Use process_rdf/3 for processing large documents in
% _|call-back|_ style.
load_rdf(File, Triples) :-
load_rdf(File, Triples, []).
load_rdf(File, Triples, M:Options0) :-
entity_options(Options0, EntOptions, Options1),
meta_options(load_meta_option, M:Options1, Options),
init_ns_collect(Options, NSList),
load_structure(File,
[ RDFElement
],
[ dialect(xmlns),
space(sgml),
call(xmlns, rdf:on_xmlns)
| EntOptions
]),
rdf_start_file(Options, Cleanup),
call_cleanup(xml_to_rdf(RDFElement, Triples0, Options),
rdf_end_file(Cleanup)),
exit_ns_collect(NSList),
post_process(Options, Triples0, Triples).
entity_options([], [], []).
entity_options([H|T0], Entities, Rest) :-
( H = entity(_,_)
-> Entities = [H|ET],
entity_options(T0, ET, Rest)
; Rest = [H|RT],
entity_options(T0, Entities, RT)
).
load_meta_option(convert_typed_literal).
%% xml_to_rdf(+XML, -Triples, +Options)
xml_to_rdf(XML, Triples, Options) :-
is_list(Options), !,
make_rdf_state(Options, State, _),
xml_to_plrdf(XML, RDF, State),
rdf_triples(RDF, Triples).
xml_to_rdf(XML, BaseURI, Triples) :-
atom(BaseURI), !,
xml_to_rdf(XML, Triples, [base_uri(BaseURI)]).
/*******************************
* POST-PROCESSING *
*******************************/
post_process([], Triples, Triples).
post_process([expand_foreach(true)|T], Triples0, Triples) :- !,
expand_each(Triples0, Triples1),
post_process(T, Triples1, Triples).
post_process([_|T], Triples0, Triples) :- !,
post_process(T, Triples0, Triples).
/*******************************
* EXPAND *
*******************************/
expand_each(Triples0, Triples) :-
select(rdf(each(Container), Pred, Object),
Triples0, Triples1), !,
each_triples(Triples1, Container, Pred, Object, Triples2),
expand_each(Triples2, Triples).
expand_each(Triples, Triples).
each_triples([], _, _, _, []).
each_triples([H0|T0], Container, P, O,
[H0, rdf(S,P,O)|T]) :-
H0 = rdf(Container, rdf:A, S),
member_attribute(A), !,
each_triples(T0, Container, P, O, T).
each_triples([H|T0], Container, P, O, [H|T]) :-
each_triples(T0, Container, P, O, T).
member_attribute(A) :-
sub_atom(A, 0, _, _, '_'). % must check number?
/*******************************
* BIG FILES *
*******************************/
%% process_rdf(+Input, :OnObject, :Options)
%
% Process RDF from Input. Input is either an atom or a term of the
% format stream(Handle). For each encountered description, call
% OnObject(+Triples) to handle the triples resulting from the
% description. Defined Options are:
%
% * base_uri(+URI)
% Determines the reference URI.
%
% * db(DB)
% When loading from a stream, the source is taken from
% this option or -if non-existent- from base_uri.
%
% * lang(LanguageID)
% Set initial language (as xml:lang)
%
% * convert_typed_literal(:Convertor)
% Call Convertor(+Type, +Content, -RDFObject) to create
% a triple rdf(S, P, RDFObject) instead of rdf(S, P,
% literal(type(Type, Content)).
%
% * namespaces(-Namespaces:list(NS=URL))
% Return list of namespaces declared using xmlns:NS=URL in
% the document. This can be used to update the namespace
% list with rdf_register_ns/2.
%
% * entity(Name, Value)
% Overrule entity values found in the file
%
% * embedded(Boolean)
% If =true=, do not give warnings if rdf:RDF is embedded
% in other XML data.
process_rdf(File, OnObject, M:Options0) :-
is_list(Options0), !,
entity_options(Options0, EntOptions, Options1),
meta_options(load_meta_option, M:Options1, Options2),
process_options(Options2, ProcessOptions, Options),
option(base_uri(BaseURI), Options, ''),
rdf_start_file(Options, Cleanup),
strip_module(OnObject, Module, Pred),
nb_setval(rdf_object_handler, Module:Pred),
nb_setval(rdf_options, Options),
nb_setval(rdf_state, -),
init_ns_collect(Options, NSList),
( File = stream(In)
-> Source = BaseURI
; is_stream(File)
-> In = File,
option(db(Source), Options, BaseURI)
; open(File, read, In, [type(binary)]),
Close = In,
Source = File
),
new_sgml_parser(Parser, [dtd(DTD)]),
def_entities(EntOptions, DTD),
set_sgml_parser(Parser, file(Source)),
set_sgml_parser(Parser, dialect(xmlns)),
set_sgml_parser(Parser, space(sgml)),
do_process_rdf(Parser, In, NSList, Close, Cleanup, ProcessOptions).
process_rdf(File, BaseURI, OnObject) :-
process_rdf(File, OnObject, [base_uri(BaseURI)]).
def_entities([], _).
def_entities([entity(Name, Value)|T], DTD) :- !,
def_entity(DTD, Name, Value),
def_entities(T, DTD).
def_entities([_|T0], DTD) :-
def_entities(T0, DTD).
def_entity(DTD, Name, Value) :-
open_dtd(DTD, [], Stream),
xml_quote_attribute(Value, QValue),
format(Stream, '<!ENTITY ~w "~w">~n', [Name, QValue]),
close(Stream).
do_process_rdf(Parser, In, NSList, Close, Cleanup, Options) :-
call_cleanup(( sgml_parse(Parser,
[ source(In),
call(begin, rdf:on_begin),
call(xmlns, rdf:on_xmlns)
| Options
]),
exit_ns_collect(NSList)
),
cleanup_process(Close, Cleanup, Parser)).
cleanup_process(In, Cleanup, Parser) :-
( var(In)
-> true
; close(In)
),
free_sgml_parser(Parser),
nb_delete(rdf_options),
nb_delete(rdf_object_handler),
nb_delete(rdf_state),
nb_delete(rdf_nslist),
rdf_end_file(Cleanup).
on_begin(NS:'RDF', Attr, _) :-
rdf_name_space(NS), !,
nb_getval(rdf_options, Options),
make_rdf_state(Options, State0, _),
rdf_modify_state(Attr, State0, State),
nb_setval(rdf_state, State).
on_begin(Tag, Attr, Parser) :-
nb_getval(rdf_state, State),
( State == (-)
-> nb_getval(rdf_options, RdfOptions),
( memberchk(embedded(true), RdfOptions)
-> true
; print_message(warning, rdf(unexpected(Tag, Parser)))
)
; get_sgml_parser(Parser, line(Start)),
get_sgml_parser(Parser, file(File)),
sgml_parse(Parser,
[ document(Content),
parse(content)
]),
nb_getval(rdf_object_handler, OnTriples),
element_to_plrdf(element(Tag, Attr, Content), Objects, State),
rdf_triples(Objects, Triples),
call(OnTriples, Triples, File:Start)
).
%% on_xmlns(+NS, +URL, +Parser)
%
% Build up the list of encountered xmlns:NS=URL declarations. We
% use destructive assignment here as an alternative to
% assert/retract, ensuring thread-safety and better performance.
on_xmlns(NS, URL, _Parser) :-
( nb_getval(rdf_nslist, List),
List = list(L0)
-> nb_linkarg(1, List, [NS=URL|L0])
; true
).
init_ns_collect(Options, NSList) :-
( option(namespaces(NSList), Options, -),
NSList \== (-)
-> nb_setval(rdf_nslist, list([]))
; nb_setval(rdf_nslist, -),
NSList = (-)
).
exit_ns_collect(NSList) :-
( NSList == (-)
-> true
; nb_getval(rdf_nslist, list(NSList))
).
process_options(Options, Process, RestOptions) :-
select_option(content_length(Len), Options, RestOptions), !,
Process = [content_length(Len)].
process_options(Options, [], Options).
/*******************************
* MESSAGES *
*******************************/
:- multifile
prolog:message/3.
% Catch messages. sgml/4 is generated by the SGML2PL binding.
prolog:message(rdf(unparsed(Data))) -->
{ phrase(unparse_xml(Data), XML)
},
[ 'RDF: Failed to interpret "~s"'-[XML] ].
prolog:message(rdf(shared_blank_nodes(N))) -->
[ 'RDF: Shared ~D blank nodes'-[N] ].
prolog:message(rdf(not_a_name(Name))) -->
[ 'RDF: argument to rdf:ID is not an XML name: ~p'-[Name] ].
prolog:message(rdf(redefined_id(Id))) -->
[ 'RDF: rdf:ID ~p: multiple definitions'-[Id] ].
prolog:message(rdf(unexpected(Tag, Parser))) -->
{ get_sgml_parser(Parser, file(File)),
get_sgml_parser(Parser, line(Line))
},
[ 'RDF: ~w:~d: Unexpected element ~w'-[File, Line, Tag] ].
/*******************************
* XML-TO-TEXT *
*******************************/
unparse_xml([]) --> !,
[].
unparse_xml([H|T]) --> !,
unparse_xml(H),
unparse_xml(T).
unparse_xml(Atom) -->
{ atom(Atom)
}, !,
atom(Atom).
unparse_xml(element(Name, Attr, Content)) -->
"<",
identifier(Name),
attributes(Attr),
( { Content == []
}
-> "/>"
; ">",
unparse_xml(Content)
).
attributes([]) -->
[].
attributes([H|T]) -->
attribute(H),
attributes(T).
attribute(Name=Value) -->
" ",
identifier(Name),
"=",
value(Value).
identifier(NS:Local) --> !,
"{", atom(NS), "}",
atom(Local).
identifier(Local) -->
atom(Local).
atom(Atom, Text, Rest) :-
atom_codes(Atom, Chars),
append(Chars, Rest, Text).
value(Value) -->
{ atom_codes(Value, Chars)
},
"\"",
quoted(Chars),
"\"".
quoted([]) -->
[].
quoted([H|T]) -->
quote(H), !,
quoted(T).
quote(0'<) --> "&lt;".
quote(0'>) --> "&gt;".
quote(0'") --> "&quot;".
quote(0'&) --> "&amp;".
quote(X) --> [X].
/*******************************
* XREF *
*******************************/
:- multifile prolog:meta_goal/2.
prolog:meta_goal(process_rdf(_,G,_), [G+2]).

475
packages/RDF/rdf2pl.doc Normal file
View File

@ -0,0 +1,475 @@
\documentclass[11pt]{article}
\usepackage{pl}
\usepackage{html}
\usepackage{times}
\onefile
\htmloutput{html} % Output directory
\htmlmainfile{index} % Main document file
\bodycolor{white} % Page colour
\newcommand{\elem}[1]{{\tt\string<#1\string>}}
\begin{document}
\title{SWI-Prolog RDF parser}
\author{Jan Wielemaker \\
HCS, \\
University of Amsterdam \\
The Netherlands \\
E-mail: \email{jan@swi-prolog.org}}
\maketitle
\begin{abstract}
\url[RDF]{http://www.w3.org/RDF/} ({\bf R}esource {\bf D}escription {\bf
F}ormat) is a \url[W3C]{http://www.w3.org/} standard for expressing
meta-data about web-resources. It has two representations providing
the same semantics. RDF documents are normally transferred as XML
documents using the RDF-XML syntax. This format is unsuitable for
processing. The parser defined here converts an RDF-XML document into
the \jargon{triple} notation. The library \pllib{rdf_write} creates
an RDF/XML document from a list of triples.
\end{abstract}
\vfill
\tableofcontents
\vfill
\vfill
\newpage
\section{Introduction}
RDF is a promising standard for representing meta-data about documents
on the web as well as exchanging frame-based data (e.g. ontologies). RDF
is often associated with `semantics on the web'. It consists of a formal
data-model defined in terms of \jargon{triples}. In addition, a
\jargon{graph} model is defined for visualisation and an XML application
is defined for exchange.
`Semantics on the web' is also associated with the Prolog programming
language. It is assumed that Prolog is a suitable vehicle to reason with
the data expressed in RDF models. Most of the related web-infra
structure (e.g. XML parsers, DOM implementations) are defined in Java,
Perl, C or C+{+}.
Various routes are available to the Prolog user. Low-level XML parsing
is due to its nature best done in C or C+{+}. These languages produce
fast code. As XML/SGML are at the basis of most of the other web-related
formats we will benefit most here. XML and SGML, being very stable
specifications, make fast compiled languages even more attractive.
But what about RDF? RDF-XML is defined in XML, and provided with a
Prolog term representing the XML document processing it according to the
RDF syntax is quick and easy in Prolog. The alternative, getting yet
another library and language attached to the system, is getting less
attractive. In this document we explore the suitability of Prolog for
processing XML documents in general and into RDF in particular.
\section{Parsing RDF in Prolog}
We realised an RDF compiler in Prolog on top of the {\bf sgml2pl}
package (providing a name-space sensitive XML parser). The
transformation is realised in two passes.
The first pass rewrites the XML term into a Prolog term conveying the
same information in a more friendly manner. This transformation is
defined in a high-level pattern matching language defined on top of
Prolog with properties similar to DCG (Definite Clause Grammar).
The source of this translation is very close to the BNF notation used by
the \url[specification]{http://www.w3.org/TR/REC-rdf-syntax/}, so
correctness is `obvious'. Below is a part of the definition for RDF
containers. Note that XML elements are represented using a term of the
format:
\begin{quote}
\term{element}{Name, [AttrName = Value...], [Content ...]}
\end{quote}
\begin{code}
memberElt(LI) ::=
\referencedItem(LI).
memberElt(LI) ::=
\inlineItem(LI).
referencedItem(LI) ::=
element(\rdf(li),
[ \resourceAttr(LI) ],
[]).
inlineItem(literal(LI)) ::=
element(\rdf(li),
[ \parseLiteral ],
LI).
inlineItem(description(description, _, _, Properties)) ::=
element(\rdf(li),
[ \parseResource ],
\propertyElts(Properties)).
inlineItem(LI) ::=
element(\rdf(li),
[],
[\rdf_object(LI)]), !. % inlined object
inlineItem(literal(LI)) ::=
element(\rdf(li),
[],
[LI]). % string value
\end{code}
Expression in the rule that are prefixed by the \verb$\$ operator acts
as invocation of another rule-set. The body-term is converted into
a term where all rule-references are replaced by variables. The
resulting term is matched and translation of the arguments is achieved
by calling the appropriate rule. Below is the Prolog code for the
{\bf referencedItem} rule:
\begin{code}
referencedItem(A, element(B, [C], [])) :-
rdf(li, B),
resourceAttr(A, C).
\end{code}
Additional code can be added using a notation close to the Prolog
DCG notation. Here is the rule for a description, producing
properties both using {\bf propAttrs} and {\bf propertyElts}.
\begin{code}
description(description, About, BagID, Properties) ::=
element(\rdf('Description'),
\attrs([ \?idAboutAttr(About),
\?bagIdAttr(BagID)
| \propAttrs(PropAttrs)
]),
\propertyElts(PropElts)),
{ !, append(PropAttrs, PropElts, Properties)
}.
\end{code}
\section{Predicates}
The parser is designed to operate in various environments and therefore
provides interfaces at various levels. First we describe the top level
defined in \pllib{rdf}, simply parsing a RDF-XML file into a list of
triples. Please note these are {\em not} asserted into the database
because it is not necessarily the final format the user wishes to reason
with and it is not clean how the user wants to deal with multiple RDF
documents. Some options are using global URI's in one pool, in Prolog
modules or using an additional argument.
\begin{description}
\predicate{load_rdf}{2}{+File, -Triples}
Same as \term{load_rdf}{File, Triples, []}.
\predicate{load_rdf}{3}{+File, -Triples, +Options}
Read the RDF-XML file \arg{File} and return a list of \arg{Triples}.
\arg{Options} defines additional processing options. Currently defined
options are:
\begin{description}
\termitem{base_uri}{BaseURI}
If provided local identifiers and identifier-references are globalised
using this URI. If omited or the atom \verb$[]$, local identifiers are
not tagged.
\termitem{blank_nodes}{Mode}
If \arg{Mode} is \const{share} (default), blank-node properties (i.e.\
complex properties without identifier) are reused if they result in
exactly the same triple-set. Two descriptions are shared if their
intermediate description is the same. This means they should produce the
same set of triples in the same order. The value \const{noshare} creates
a new resource for each blank node.
\termitem{expand_foreach}{Boolean}
If \arg{Boolean} is \const{true}, expand \const{rdf:aboutEach} into
a set of triples. By default the parser generates
\term{rdf}{each(Container), Predicate, Subject}.
\termitem{lang}{Lang}
Define the initial language (i.e.\ pretend there is an \const{xml:lang}
declaration in an enclosing element).
\termitem{ignore_lang}{Bool}
If \const{true}, \const{xml:lang} declarations in the document are
ignored. This is mostly for compatibility with older versions of
this library that did not support language identifiers.
\termitem{convert_typed_literal}{:ConvertPred}
If the parser finds a literal with the \const{rdf:datatype}=\arg{Type}
attribute, call \term{ConvertPred}{+Type, +Content, -Literal}.
\arg{Content} is the XML element contentas returned by the XML
parser (a list). The predicate must unify \arg{Literal}
with a Prolog representation of \arg{Content} according to
\arg{Type} or throw an exception if the conversion cannot be made.
This option servers two purposes. First of all it can be used
to ignore type declarations for backward compatibility of this
library. Second it can be used to convert typed literals to
a meaningful Prolog representation. E.g.\ convert '42' to the
Prolog integer 42 if the type is \const{xsd:int} or a related
type.
\termitem{namespaces}{-List}
Unify \arg{List} with a list of \arg{NS}=\arg{URL} for each
encountered \const{xmlns}:\arg{NS}=\arg{URL} declaration found
in the source.
\termitem{entity}{+Name, +Value}
Overrule entity declaration in file. As it is common practice
to declare namespaces using entities in RDF/XML, this option
allows for changing the namespace without changing the file.
Multiple of these options are allowed.
\end{description}
The \arg{Triples} list is a list of \term{rdf}{Subject, Predicate,
Object} triples. \arg{Subject} is either a plain resource (an atom),
or one of the terms \term{each}{URI} or \term{prefix}{URI} with the
obvious meaning. \arg{Predicate} is either a plain atom for
explicitely non-qualified names or a term
\mbox{\arg{NameSpace}{\bf :}\arg{Name}}. If \arg{NameSpace} is the
defined RDF name space it is returned as the atom \const{rdf}.
Finally, \arg{Object} is a URI, a \arg{Predicate} or a term of the
format \term{literal}{Value} for literal values. \arg{Value} is
either a plain atom or a parsed XML term (list of atoms and elements).
\end{description}
\subsection{RDF Object representation} \label{sec:rdfobject}
The \emph{Object} (3rd) part of a triple can have several different
types. If the object is a resource it is returned as either a plain
atom or a term \mbox{\arg{NameSpace}{\bf :}\arg{Name}}. If it is a
literal it is returned as \term{literal}{Value}, where \arg{Value}
takes one of the formats defined below.
\begin{itemlist}
\item [An atom]
If the literal \arg{Value} is a plain atom is a literal value not
subject to a datatype or \const{xml:lang} qualifier.
\item [\term{lang}{LanguageID, Atom}]
If the literal is subject to an \const{xml:lang} qualifier
\arg{LanguageID} specifies the language and \arg{Atom} the
actual text.
\item [A list]
If the literal is an XML literal as created by
\mbox{parseType="Literal"}, the raw output of the XML parser for the
content of the element is returned. This content is a list of
\term{element}{Name, Attributes, Content} and atoms for CDATA parts as
described with the SWI-Prolog \url[SGML/XML
parser]{http://www.swi-prolog.org/packages/sgml2pl.html}
\item [\term{type}{Type, StringValue}]
If the literal has an \verb$rdf:datatype=$\arg{Type} a term of this
format is returned.
\end{itemlist}
\subsection{Name spaces}
XML name spaces are identified using a URI. Unfortunately various URI's
are in common use to refer to RDF. The \file{rdf_parser.pl} module
therefore defines the namespace as a multifile/1 predicate, that can be
extended by the user. For example, to parse the \url[Netscape
OpenDirectory]{http://www.mozilla.org/rdf/doc/inference.html}
\file{structure.rdf} file, the following declarations are used:
\begin{code}
:- multifile
rdf_parser:rdf_name_space/1.
rdf_parser:rdf_name_space('http://www.w3.org/TR/RDF/').
rdf_parser:rdf_name_space('http://directory.mozilla.org/rdf').
rdf_parser:rdf_name_space('http://dmoz.org/rdf').
\end{code}
The initial definition of this predicate is given below.
\begin{code}
rdf_name_space('http://www.w3.org/1999/02/22-rdf-syntax-ns#').
rdf_name_space('http://www.w3.org/TR/REC-rdf-syntax').
\end{code}
\subsection{Low-level access}
The above defined load_rdf/[2,3] is not always suitable. For example, it
cannot deal with documents where the RDF statement is embedded in an XML
document. It also cannot deal with really large documents (e.g.\ the
Netscape OpenDirectory project, currently about 90 MBytes), without huge
amounts of memory.
For really large documents, the {\bf sgml2pl} parser can be programmed
to handle the content of a specific element (i.e. \elem{rdf:RDF})
element-by-element. The parsing primitives defined in this section
can be used to process these one-by-one.
\begin{description}
\predicate{xml_to_rdf}{3}{+XML, +BaseURI, -Triples}
Process an XML term produced by load_structure/3 using the
\term{dialect}{xmlns} output option. \arg{XML} is either
a complete \elem{rdf:RDF} element, a list of RDF-objects
(container or description) or a single description of container.
\predicate{process_rdf}{3}{+Input, :OnTriples, +Options}
Exploits the call-back interface of {\bf sgml2pl}, calling
\term{\arg{OnTriples}}{Triples, File:Line} with the list of triples
resulting from a single top level RDF object for each RDF element in the
input as well as the source-location where the description started.
\arg{Input} is either a file name or term \term{stream}{Stream}. When
using a stream all triples are associated to the value of the
\const{base_uri} option. This predicate can be used to process arbitrary
large RDF files as the file is processed object-by-object. The example
below simply asserts all triples into the database:
\begin{code}
assert_list([], _).
assert_list([H|T], Source) :-
assert(H),
assert_list(T, Source).
?- process_rdf('structure,rdf', assert_list, []).
\end{code}
\arg{Options} are described with load_rdf/3. The option
\const{expand_foreach} is not supported as the container may be in a
different description. Additional it provides \const{embedded}:
\begin{description}
\termitem{embedded}{Boolean}
The predicate process_rdf/3 processes arbitrary XML documents, only
interpreting the content of \const{rdf:RDF} elements. If this option
is \const{false} (default), it gives a warning on elements that are
not processed. The option \term{embedded}{true} can be used to
process RDF embedded in \jargon{xhtml} without warnings.
\end{description}
\end{description}
\section{Writing RDF graphs}
The library \pllib{rdf_write} provides the inverse of load_rdf/2 using
the predicate rdf_write_xml/2. In most cases the RDF parser is used in
combination with the Semweb package providing \pllib{semweb/rdf_db}.
This library defines rdf_save/2 to save a named RDF graph from the
database to a file. This library writes a list of rdf terms to a stream.
It has been developed for the SeRQL server which computes an RDF graph
that needs to be transmitted in an HTTP request. As we see this as a
typical use-case scenario the library only provides writing to a stream.
\begin{description}
\predicate{rdf_write_xml}{2}{+Stream, +Triples}
Write an RDF/XML document to \arg{Stream} from the list of \arg{Triples}.
\arg{Stream} must use one of the following Prolog stream encodings:
\const{ascii}, \const{iso_latin_1} or \const{utf8}. Characters that
cannot be represented in the encoding are represented as XML entities.
Using ASCII is a good idea for documents that can be represented almost
completely in ASCII. For more international documents using UTF-8 creates
a more compact document that is easier to read.
\begin{code}
rdf_write(File, Triples) :-
open(File, write, Out, [encoding(utf8)]),
call_cleanup(rdf_write_xml(Out, Triples),
close(Out)).
\end{code}
\end{description}
\section{Testing the RDF translator}
A test-suite and driver program are provided by \file{rdf_test.pl} in
the source directory. To run these tests, load this file into Prolog in
the distribution directory. The test files are in the directory
\file{suite} and the proper output in \file{suite/ok}. Predicates
provided by \file{rdf_test.pl}:
\begin{description}
\predicate{suite}{1}{+N}
Run test \arg{N} using the file \file{suite/tN.rdf} and display the
RDF source, the intermediate Prolog representation and the resulting
triples.
\predicate{passed}{1}{+N}
Process \file{suite/tN.rdf} and store the resulting triples in
\file{suite/ok/tN.pl} for later validation by test/0.
\predicate{test}{0}{}
Run all tests and classify the result.
\end{description}
\appendix
\section{Metrics}
It took three days to write and one to document the Prolog RDF parser.
A significant part of the time was spent understanding the RDF
specification.
The size of the source (including comments) is given in the table
below.
\begin{center}
\begin{tabular}{|rrr|l|l|}
\hline
\bf lines & \bf words & \bf bytes & \bf file & \bf function \\
\hline
109 & 255 & 2663 & rdf.pl & Driver program \\
312 & 649 & 6416 & rdf_parser.pl & 1-st phase parser \\
246 & 752 & 5852 & rdf_triple.pl & 2-nd phase parser \\
126 & 339 & 2596 & rewrite.pl & rule-compiler \\
\hline
793 & 1995 & 17527 & total & \\
\hline
\end{tabular}
\end{center}
We also compared the performance using an RDF-Schema file generated by
\url[Protege-2000]{http://www.smi.stanford.edu/projects/protege/} and
interpreted as RDF. This file contains 162 descriptions in 50 Kbytes,
resulting in 599 triples. Environment: Intel Pentium-II/450 with
384 Mbytes memory running SuSE Linux 6.3.
The parser described here requires 0.15 seconds excluding 0.13 seconds
Prolog startup time to process this file. The \url[Pro
Solutions]{http://www.pro-solutions.com/rdfdemo/} parser (written in
Perl) requires 1.5 seconds exluding 0.25 seconds startup time.
\section{Installation}
\subsection{Unix systems}
Installation on Unix system uses the commonly found {\em configure},
{\em make} and {\em make install} sequence. SWI-Prolog should be
installed before building this package. If SWI-Prolog is not installed
as \program{pl}, the environment variable \env{PL} must be set to the
name of the SWI-Prolog executable. Installation is now accomplished
using:
\begin{code}
% ./configure
% make
% make install
\end{code}
This installs the Prolog library files in \file{$PLBASE/library}, where
\file{$PLBASE} refers to the SWI-Prolog `home-directory'.
\subsection{Windows}
Run the file \file{setup.pl} by double clicking it. This will install
the required files into the SWI-Prolog directory and update the
library directory.
\end{document}

509
packages/RDF/rdf_diagram.pl Normal file
View File

@ -0,0 +1,509 @@
/* Part of SWI-Prolog
Author: Jan Wielemaker
E-mail: J.Wielemaker@uva.nl
WWW: http://www.swi-prolog.org
Copyright (C): 2010, University of Amsterdam
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
as published by the Free Software Foundation; either version 2
of the License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
As a special exception, if you link this library with other files,
compiled with a Free Software compiler, to produce an executable, this
library does not by itself cause the resulting executable to be covered
by the GNU General Public License. This exception does not however
invalidate any other reasons why the executable file might be covered by
the GNU General Public License.
*/
:- module(rdf_diagram,
[ rdf_diagram_from_file/1 % +File
]).
:- use_module(library(pce)).
:- use_module(library(pce_tagged_connection)).
:- use_module(library(autowin)).
:- use_module(library(pce_report)).
:- use_module(library(print_graphics)).
:- use_module(library(rdf_parser)). % get access to declared namespaces
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
This file defines the class rdf_diagram, a window capable of showing a
set of triples.
The predicate rdf_diagram_from_file(+File) is a simple demo and useful
tool to show RDF from simple RDF files.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
/*******************************
* SIMPLE ENTRY *
*******************************/
% rdf_diagram_from_file(+File)
%
% Show the triples from File in a window.
rdf_diagram_from_file(File) :-
absolute_file_name(File,
[ access(read),
extensions([rdf,rdfs,owl,''])
], AbsFile),
load_rdf(AbsFile, Triples,
[ expand_foreach(true)
]),
new(D, rdf_diagram(string('RDF diagram for %s', File))),
send(new(report_dialog), below, D),
send(D, triples, Triples),
send(D, open).
/*******************************
* CLASS RDF-DIAGRAM *
*******************************/
:- pce_begin_class(rdf_diagram, auto_sized_picture,
"Show set of RDF triples in a window").
:- use_class_template(print_graphics).
variable(auto_layout, bool := @on, both, "Automatically layout on resize").
variable(type_in_node, bool := @on, both, "Display type inside node").
initialise(D, Label:[name]) :->
send_super(D, initialise, Label),
send(D, scrollbars, both),
send(D, fill_popup),
send(D, resize_message,
if(and(D?auto_layout == @on,
D?focus_recogniser == @nil),
message(D, layout))).
fill_popup(D) :->
send(D, popup, new(P, popup)),
send_list(P, append,
[ menu_item(layout, message(D, layout)),
gap,
menu_item(print, message(D, print))
]).
:- pce_group(triples).
append(D, Triple:prolog) :->
"Append and rdf(Subject, Predicate, Object) triple"::
( subject_name(Triple, SubjectName),
get(D, resource, SubjectName, Subject),
( get(D, type_in_node, @on),
is_type(Triple)
-> object_resource(Triple, ObjectName),
send(Subject, type, ObjectName)
; predicate_name(Triple, PredName),
( object_resource(Triple, ObjectName)
-> get(D, resource, ObjectName, Object)
; object_literal(Triple, Literal)
-> get(D, literal, Literal, Object)
),
send(Subject, connect, PredName, Object)
)
-> true
; term_to_atom(Triple, Atom),
ignore(send(D, report, error,
'Failed to display triple: %s', Atom))
).
triples(D, Triples:prolog) :->
"Show disgram from Prolog triples"::
send(D, clear),
forall(member(T, Triples),
send(D, append, T)),
send(D, layout).
resource(D, Resource:name) :->
"Add Resource to diagram"::
get(D, resource, Resource, @on, _).
resource(D, Resource:name, Create:[bool], Subject:rdf_resource) :<-
"Get reference for a subject or create one"::
( get(D, member, Resource, Subject)
-> true
; Create \== @off,
get(D, create_resource, Resource, Subject),
send(D, display, Subject, D?visible?center)
).
literal(D, Value:prolog, Gr:rdf_literal) :<-
"Display a literal. Don't try to re-use"::
( literal_name(Value, Name),
get(D, member, Name, Gr)
-> true
; get(D, create_literal, Value, Gr),
send(D, display, Gr, D?visible?center)
).
create_resource(D, Resource:name, Subject:rdf_resource) :<-
"Create visualisation of Resource"::
new(Subject, rdf_resource(Resource, D)).
create_literal(_D, Value:prolog, Gr:rdf_literal) :<-
"Create visualisation of literal"::
new(Gr, rdf_literal(Value)).
node_label(_D, Resource:name, Label:name) :<-
"Generate label to show for a node"::
local_name(Resource, Label).
:- pce_group(layout).
layout(D) :->
"Produce automatic layout"::
new(Nodes, chain),
send(D?graphicals, for_all,
if(message(@arg1, instance_of, rdf_any),
message(Nodes, append, @arg1))),
send(Nodes?head, layout, 2, 40,
iterations := 200,
area := D?visible,
network := Nodes).
copy_layout(D, From:rdf_diagram, Subst:prolog) :->
"Copy the layout from another windows"::
send(D?graphicals, for_some,
message(D, copy_location, @arg1, From, prolog(Subst))).
copy_location(_D, Obj:graphical, From:rdf_diagram, Subst:prolog) :->
"Copy location of a single RDF object"::
( send(Obj, instance_of, rdf_any)
-> ( get(Obj, name, Name),
find(From, Name, Subst, FromObj)
-> format('Copied location of ~p from ~p~n', [Obj, FromObj]),
get(FromObj, center, Center),
send(Obj, center, Center)
)
; true
).
find(D, Name, _Subst, Obj) :-
get(D, member, Name, Obj).
find(D, Name, Subst, Obj) :-
member(Name=AltName, Subst),
atom_concat('_:', AltName, FullAltName),
get(D, member, FullAltName, Obj).
find(D, Name, Subst, _) :-
format('Cannot find ~w in ~p, Subst =~n', [Name, D]),
pp(Subst),
fail.
:- pce_end_class(rdf_diagram).
/*******************************
* SHAPES *
*******************************/
:- pce_begin_class(rdf_connection, tagged_connection,
"Represents a triple").
:- pce_global(@rdf_link, new(link(link, link,
line(0,0,0,0,second)))).
initialise(C, Gr1:graphical, Gr2:graphical, Pred:name, Ctx:[object]) :->
"Create from predicate"::
send_super(C, initialise, Gr1, Gr2, @rdf_link),
send(C, tag, rdf_label(Pred, italic, Ctx)).
ideal_length(C, Len:int) :<-
"Layout: compute the desired length"::
get(C, height, H),
( H < 40
-> get(C, tag, Tag),
get(Tag, width, W),
Len is W + 30
; Len = 40
).
:- pce_end_class(rdf_connection).
:- pce_begin_class(rdf_any(name), figure,
"Represent an RDF resource or literal").
handle(w/2, 0, link, north).
handle(w, h/2, link, east).
handle(w/2, h, link, south).
handle(0, h/2, link, west).
initialise(F, Ref:name) :->
"Create visualisation"::
send_super(F, initialise),
send(F, name, Ref).
connect(F, Pred:name, Object:graphical) :->
new(_C, rdf_connection(F, Object, Pred, F)).
:- pce_global(@rdf_any_recogniser,
make_rdf_any_recogniser).
:- pce_global(@rdf_any_popup,
make_rdf_any_popup).
make_rdf_any_recogniser(G) :-
new(M1, move_gesture(left)),
new(M2, move_network_gesture(left, c)),
new(P, popup_gesture(@receiver?popup)),
new(G, handler_group(M1, M2, P)).
popup(_F, Popup:popup) :<-
"Create popup menu"::
Popup = @rdf_any_popup.
make_rdf_any_popup(Popup) :-
new(Popup, popup),
Gr = @arg1,
send(Popup, append,
menu_item(layout, message(Gr, layout))).
event(F, Ev:event) :->
( \+ send(Ev, is_a, ms_right_down),
send_super(F, event, Ev)
-> true
; send(@rdf_any_recogniser, event, Ev)
).
node_label(F, Resource:name, Label:name) :<-
"Return label to use for a resource"::
get(F, device, Dev),
( send(Dev, has_get_method, node_label)
-> get(Dev, node_label, Resource, Label)
; local_name(Resource, Label)
).
:- pce_end_class(rdf_any).
:- pce_begin_class(move_network_gesture, move_gesture,
"Move network of connected graphicals").
variable(outline, box, get,
"Box used to indicate move").
variable(network, chain*, both,
"Stored value of the network").
variable(origin, point, get,
"Start origin of network").
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
The gesture maintains an outline, the selection to be moved and the
positon where the move orginiated. The outline itself is given a
normal move_gesture to make it move on dragging. This move_gesture
should operate on the same button and modifier.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
initialise(G, B:[button_name], M:[modifier]) :->
send(G, send_super, initialise, B, M),
send(G, slot, outline, new(Box, box(0,0))),
send(G, slot, origin, point(0,0)),
send(Box, texture, dotted),
send(Box, recogniser, move_gesture(G?button, G?modifier)).
initiate(G, Ev:event) :->
get(Ev, receiver, Gr),
get(Gr, device, Dev),
get(G, outline, Outline),
get(Gr, network, Network),
send(G, network, Network),
new(Union, area(0,0,0,0)),
send(Network, for_all, message(Union, union, @arg1?area)),
send(G?origin, copy, Union?position),
send(Outline, area, Union),
send(Union, done),
send(Dev, display, Outline),
ignore(send(Ev, post, Outline)).
drag(G, Ev) :->
send(Ev, post, G?outline).
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
Terminate. First undisplay the outline. Next calculate by how much
the outline has been dragged and move all objects of the selection by
this amount.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
terminate(G, Ev:event) :->
ignore(send(G, drag, Ev)),
get(G, outline, Outline),
send(Outline, device, @nil),
get(Outline?area?position, difference, G?origin, Offset),
get(G, network, Network),
send(Network, for_all, message(@arg1, relative_move, Offset)),
send(G, network, @nil).
:- pce_end_class(move_network_gesture).
:- pce_begin_class(rdf_label, text,
"Label for an RDF relation").
variable(resource, name, get, "Represented predicate").
initialise(L, Pred:name, Font:font, Context:[object]) :->
( Context == @default
-> local_name(Pred, Label)
; get(Context, node_label, Pred, Label)
),
send_super(L, initialise, Label, center, Font),
send(L, slot, resource, Pred),
send(L, background, @default).
:- pce_global(@rdf_label_recogniser,
make_rdf_label_recogniser).
make_rdf_label_recogniser(G) :-
new(G, handler_group),
send(G, append,
handler(area_enter, message(@receiver, identify))),
send(G, append,
handler(area_exit, message(@receiver, report, status, ''))),
send(G, append, popup_gesture(new(P, popup))),
send_list(P, append,
[ menu_item(copy,
message(@display, copy, @arg1?resource))
]).
event(F, Ev:event) :->
( send_super(F, event, Ev)
-> true
; send(@rdf_label_recogniser, event, Ev)
).
identify(L) :->
send(L, report, status, '%s', L?resource).
:- pce_end_class.
:- pce_begin_class(rdf_resource, rdf_any,
"Represent an RDF resource").
initialise(F, Ref:name, Ctx:[object]) :->
"Create visualisation"::
send_super(F, initialise, Ref),
send(F, display, ellipse(100, 50), point(-50,-25)),
send(F, display, new(T, rdf_label(Ref, normal, Ctx))),
send(T, center, point(0,0)).
type(F, Type:name) :->
send(F, display, new(TL, rdf_label(Type, small, F))),
send(TL, center, point(0,14)),
get(F, member, ellipse, E),
send(E, shadow, 2).
identify(F) :->
send(F, report, status, 'Resource %s', F?name).
:- pce_end_class(rdf_resource).
:- pce_begin_class(rdf_literal, rdf_any,
"Represent an RDF literal value").
variable(value, prolog, get, "Represented literal value").
initialise(F, Value:prolog) :->
"Create visualisation"::
send(F, slot, value, Value),
literal_label(Value, Label),
atom_concat('__lit:', Label, Id),
send_super(F, initialise, Id),
send(F, display, new(B, box)),
send(B, fill_pattern, colour(grey80)),
send(B, pen, 0),
send(F, display, new(T, text(Label, center))),
send(T, center, point(0,0)),
send(F, fit).
literal_label(literal(Value0), Value) :- !,
literal_label(Value0, Value).
literal_label(xml(Value0), Value) :- !,
literal_label(Value0, Value).
literal_label(Value, Value) :-
atomic(Value), !.
literal_label(Value, Label) :-
term_to_atom(Value, Label).
literal_name(Value, Name) :-
literal_label(Value, Label),
atom_concat('__lit:', Label, Name).
fit(F) :->
"Make box fit contents"::
get(F, member, text, Text),
get(Text?area, clone, Area),
send(Area, increase, 3),
get(F, member, box, Box),
send(Box, area, Area).
:- pce_end_class(rdf_literal).
/*******************************
* PRIMITIVES *
*******************************/
subject_name(rdf(Name0, _, _), Name) :-
resource_name(Name0, Name).
predicate_name(rdf(_, Name0, _), Name) :-
resource_name(Name0, Name).
object_resource(rdf(_, _, Name0), Name) :-
resource_name(Name0, Name).
object_literal(rdf(_,_,Literal), Literal).
resource_name(Name, Name) :-
atom(Name), !.
resource_name(rdf:Local, Name) :- !, % known namespaces
atomic_list_concat([rdf, :, Local], Name).
resource_name(NS:Local, Name) :- !,
atom_concat(NS, Local, Name).
resource_name(node(Anon), Name) :- % Not for predicates
atom_concat('_:', Anon, Name).
is_type(rdf(_, rdf:type, _)) :- !. % our parser
is_type(rdf(_, Pred, _)) :- % our parser
atom(Pred),
rdf_name_space(NS),
atom_concat(NS, type, Pred), !.
% local_name(+Resource, -Label)
%
% Return easy readable local name
local_name(Resource, Local) :-
sub_atom(Resource, _, _, A, #),
sub_atom(Resource, _, A, 0, Local),
\+ sub_atom(Local, _, _, _, #), !.
local_name(Resource, Local) :-
atom_concat('rdf:', Local, Resource), !.
local_name(Resource, Local) :-
file_base_name(Resource, Local),
Local \== ''.
local_name(Resource, Resource).

View File

@ -0,0 +1,342 @@
/* Part of SWI-Prolog
Author: Jan Wielemaker
E-mail: J.Wielemaker@uva.nl
WWW: http://www.swi-prolog.org
Copyright (C): 2010, University of Amsterdam
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
as published by the Free Software Foundation; either version 2
of the License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
As a special exception, if you link this library with other files,
compiled with a Free Software compiler, to produce an executable, this
library does not by itself cause the resulting executable to be covered
by the GNU General Public License. This exception does not however
invalidate any other reasons why the executable file might be covered by
the GNU General Public License.
*/
:- module(rdf_ntriples,
[ load_rdf_ntriples/2, % +File, -Triples
rdf_ntriple_part/4 % +Field, -Value, <DCG>
]).
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
This module parses n-triple files as defined by the W3C RDF working in
http://www.w3.org/TR/rdf-testcases/#ntriples. This format is a
simplified version of the RDF N3 notation used in the *.nt files that
are used to describe the normative outcome of the RDF test-cases.
The returned list terms are of the form
rdf(Subject, Predicate, Object)
where
# Subject
is an atom or node(Id) for anonymous nodes
# Predicate
is an atom
# Object
is an atom, node(Id), literal(Atom) or xml(Atom)
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
% load_rdf_ntriples(+Source, -Triples)
%
% Load a file or stream to a list of rdf(S,P,O) triples.
load_rdf_ntriples(File, Triples) :-
open_nt_file(File, In, Close),
call_cleanup(stream_to_triples(In, Triples), Close).
% open_nt_file(+Input, -Stream, -Close)
%
% Open Input, returning Stream and a goal to cleanup Stream if it
% was opened.
open_nt_file(stream(Stream), Stream, true) :- !.
open_nt_file(Stream, Stream, true) :-
is_stream(Stream), !.
open_nt_file(Spec, Stream, close(Stream)) :-
absolute_file_name(Spec,
[ access(read),
extensions([nt,''])
], Path),
open(Path, read, Stream).
% rdf_ntriple_part(+Type, -Value, <DCG>)
%
% Parse one of the fields of an ntriple. This is used for the
% SWI-Prolog Sesame (www.openrdf.org) implementation to realise
% /servlets/removeStatements. I do not think public use of this
% predicate should be stimulated.
rdf_ntriple_part(subject, Subject) -->
subject(Subject).
rdf_ntriple_part(predicate, Predicate) -->
predicate(Predicate).
rdf_ntriple_part(object, Object) -->
predicate(Object).
% stream_to_triples(+Stream, -ListOfTriples)
%
% Read Stream, returning all its triples
stream_to_triples(In, Triples) :-
read_line_to_codes(In, Line),
( Line == end_of_file
-> Triples = []
; phrase(line(Triples, Tail), Line),
stream_to_triples(In, Tail)
).
line(Triples, Tail) -->
wss,
( comment
-> {Triples = Tail}
; triple(Triple)
-> {Triples = [Triple|Tail]}
).
comment -->
"#", !,
skip_rest.
comment -->
end_of_input.
triple(rdf(Subject, Predicate, Object)) -->
subject(Subject), ws, wss,
predicate(Predicate), ws, wss,
object(Object), wss, ".", wss.
subject(Subject) -->
uniref(Subject), !.
subject(Subject) -->
node_id(Subject).
predicate(Predicate) -->
uniref(Predicate).
object(Object) -->
uniref(Object), !.
object(Object) -->
node_id(Object).
object(Object) -->
literal(Object).
uniref(URI) -->
"<",
escaped_uri_codes(Codes),
">", !,
{ atom_codes(URI, Codes)
}.
node_id(node(Id)) --> % anonymous nodes
"_:",
name_start(C0),
name_codes(Codes),
{ atom_codes(Id, [C0|Codes])
}.
literal(Literal) -->
lang_string(Literal), !.
literal(Literal) -->
xml_string(Literal).
% name_start(-Code)
% name_codes(-ListfCodes)
%
% Parse identifier names
name_start(C) -->
[C],
{ code_type(C, alpha)
}.
name_codes([C|T]) -->
[C],
{ code_type(C, alnum)
}, !,
name_codes(T).
name_codes([]) -->
[].
% escaped_uri_codes(-CodeList)
%
% Decode string holding %xx escaped characters.
escaped_uri_codes([]) -->
[].
escaped_uri_codes([C|T]) -->
"%", [D0,D1], !,
{ code_type(D0, xdigit(V0)),
code_type(D1, xdigit(V1)),
C is V0<<4 + V1
},
escaped_uri_codes(T).
escaped_uri_codes([C|T]) -->
"\\u", [D0,D1,D2,D3], !,
{ code_type(D0, xdigit(V0)),
code_type(D1, xdigit(V1)),
code_type(D2, xdigit(V2)),
code_type(D3, xdigit(V3)),
C is V0<<12 + V1<<8 + V2<<4 + V3
},
escaped_uri_codes(T).
escaped_uri_codes([C|T]) -->
"\\U", [D0,D1,D2,D3,D4,D5,D6,D7], !,
{ code_type(D0, xdigit(V0)),
code_type(D1, xdigit(V1)),
code_type(D2, xdigit(V2)),
code_type(D3, xdigit(V3)),
code_type(D4, xdigit(V4)),
code_type(D5, xdigit(V5)),
code_type(D6, xdigit(V6)),
code_type(D7, xdigit(V7)),
C is V0<<28 + V1<<24 + V2<<20 + V3<<16 +
V4<<12 + V5<<8 + V6<<4 + V7
},
escaped_uri_codes(T).
escaped_uri_codes([C|T]) -->
[C],
escaped_uri_codes(T).
% lang_string()
%
% Process a language string
lang_string(String) -->
"\"",
string(Codes),
"\"", !,
{ atom_codes(Atom, Codes)
},
( langsep
-> language(Lang),
{ String = literal(lang(Lang, Atom))
}
; "^^"
-> uniref(Type),
{ String = literal(type(Type, Atom))
}
; { String = literal(Atom)
}
).
langsep -->
"-".
langsep -->
"@".
% xml_string(String)
%
% Handle xml"..."
xml_string(xml(String)) -->
"xml\"", % really no whitespace?
string(Codes),
"\"",
{ atom_codes(String, Codes)
}.
string([]) -->
[].
string([C0|T]) -->
string_char(C0),
string(T).
string_char(0'\\) -->
"\\\\".
string_char(0'") -->
"\\\"".
string_char(10) -->
"\\n".
string_char(13) -->
"\\r".
string_char(9) -->
"\\t".
string_char(C) -->
"\\u",
'4xdigits'(C).
string_char(C) -->
"\\U",
'4xdigits'(C0),
'4xdigits'(C1),
{ C is C0<<16 + C1
}.
string_char(C) -->
[C].
'4xdigits'(C) -->
[C0,C1,C2,C3],
{ code_type(C0, xdigit(V0)),
code_type(C1, xdigit(V1)),
code_type(C2, xdigit(V2)),
code_type(C3, xdigit(V3)),
C is V0<<12 + V1<<8 + V2<<4 + V3
}.
% language(-Lang)
%
% Return xml:lang language identifier.
language(Lang) -->
lang_code(C0),
lang_codes(Codes),
{ atom_codes(Lang, [C0|Codes])
}.
lang_code(C) -->
[C],
{ C \== 0'.,
\+ code_type(C, white)
}.
lang_codes([C|T]) -->
lang_code(C), !,
lang_codes(T).
lang_codes([]) -->
[].
/*******************************
* BASICS *
*******************************/
skip_rest(_,[]).
ws -->
[C],
{ code_type(C, white)
}.
end_of_input([], []).
wss -->
ws, !,
wss.
wss -->
[].

632
packages/RDF/rdf_parser.pl Normal file
View File

@ -0,0 +1,632 @@
/* $Id$
Part of SWI-Prolog
Author: Jan Wielemaker
E-mail: J.Wielemaker@cs.vu.nl
WWW: http://www.swi-prolog.org
Copyright (C): 2002-2009, University of Amsterdam
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
as published by the Free Software Foundation; either version 2
of the License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU Lesser General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
As a special exception, if you link this library with other files,
compiled with a Free Software compiler, to produce an executable, this
library does not by itself cause the resulting executable to be covered
by the GNU General Public License. This exception does not however
invalidate any other reasons why the executable file might be covered by
the GNU General Public License.
*/
:- module(rdf_parser,
[ xml_to_plrdf/3, % +XMLTerm, -RDFTerm, +State
element_to_plrdf/3, % +ContentList, -RDFTerm, +State
make_rdf_state/3, % +Options, -State, -RestOptions
rdf_modify_state/3, % +XMLAttrs, +State0, -State
rdf_name_space/1
]).
:- use_module(rewrite).
:- use_module(library(sgml)). % xml_name/1
:- use_module(library(lists)).
:- use_module(library(uri)).
:- use_module(library(record)).
:- op(500, fx, \?). % Optional (attrs)
term_expansion(F, T) :- rew_term_expansion(F, T).
goal_expansion(F, T) :- rew_goal_expansion(F, T).
goal_expansion(attrs(Attrs, List), Goal) :-
translate_attrs(List, Attrs, Goal).
translate_attrs(Var, Attrs, rewrite(Var, Attrs)) :-
var(Var), !.
translate_attrs([], _, true) :- !.
translate_attrs([H], Attrs, Goal) :- !,
( var(H)
-> Goal = rewrite(H, Attrs)
; H = \?Optional
-> Goal = ( member(A, Attrs),
OptRewrite
-> true
; true
),
expand_goal(rewrite(\Optional, A), OptRewrite)
; Goal = ( member(A, Attrs),
Rewrite
-> true
),
expand_goal(rewrite(H, A), Rewrite)
).
translate_attrs([H|T], Attrs0, (G0, G1)) :- !,
( var(H)
-> G0 = rewrite(H, Attrs0),
Attrs1 = Attrs0
; H = \?Optional
-> G0 = ( select(A, Attrs0, Attrs1),
OptRewrite
-> true
; Attrs1 = Attrs0
),
expand_goal(rewrite(\Optional, A), OptRewrite)
; G0 = ( select(A, Attrs0, Attrs1),
Rewrite
),
expand_goal(rewrite(H, A), Rewrite)
),
translate_attrs(T, Attrs1, G1).
translate_attrs(Rule, Attrs, Goal) :-
expand_goal(rewrite(Rule, Attrs), Goal).
:- multifile rdf_name_space/1.
:- dynamic rdf_name_space/1.
%% rdf_name_space(?URL) is nondet.
%
% True if URL must be handled as rdf: Determines special handling
% of rdf:about, rdf:resource, etc.
rdf_name_space('http://www.w3.org/1999/02/22-rdf-syntax-ns#').
rdf_name_space('http://www.w3.org/TR/REC-rdf-syntax').
:- record
rdf_state(base_uri='',
lang='',
ignore_lang=false,
convert_typed_literal).
%% xml_to_plrdf(+RDFElementOrObject, -RDFTerm, +State)
%
% Translate an XML (using namespaces) term into an Prolog term
% representing the RDF data. This term can then be fed into
% rdf_triples/[2,3] to create a list of RDF triples. State is an
% instance of an rdf_state record.
xml_to_plrdf(Element, RDF, State) :-
( is_list(Element)
-> rewrite(\xml_content_objects(RDF, State), Element)
; rewrite(\xml_objects(RDF, State), Element)
).
%% element_to_plrdf(+DOM, -RDFTerm, +State)
%
% Rewrite a single XML element.
element_to_plrdf(Element, RDF, State) :-
rewrite(\nodeElementList(RDF, State), [Element]).
xml_objects(Objects, Options0) ::=
E0,
{ modify_state(E0, Options0, E, Options), !,
rewrite(\xml_objects(Objects, Options), E)
}.
xml_objects(Objects, Options) ::=
element((\rdf('RDF'), !),
_,
\nodeElementList(Objects, Options)),
!.
xml_objects(Objects, Options) ::=
element(_, _, \xml_content_objects(Objects, Options)).
xml_content_objects([], _) ::=
[].
xml_content_objects([H|T], Options) ::=
[ \xml_objects(H, Options)
| \xml_content_objects(T, Options)
].
nodeElementList([], _Options) ::=
[], !.
nodeElementList(L, Options) ::=
[ (\ws, !)
| \nodeElementList(L, Options)
].
nodeElementList([H|T], Options) ::=
[ \nodeElementOrError(H, Options)
| \nodeElementList(T, Options)
].
nodeElementOrError(H, Options) ::=
\nodeElement(H, Options), !.
nodeElementOrError(unparsed(Data), _Options) ::=
Data.
nodeElement(description(Type, About, Properties), Options) ::=
\description(Type, About, Properties, Options).
/*******************************
* DESCRIPTION *
*******************************/
description(Type, About, Properties, Options0) ::=
E0,
{ modify_state(E0, Options0, E, Options), !,
rewrite(\description(Type, About, Properties, Options), E)
}.
description(description, About, Properties, Options) ::=
element(\rdf('Description'),
\attrs([ \?idAboutAttr(About, Options)
| \propAttrs(PropAttrs, Options)
]),
\propertyElts(PropElts, Options)),
{ !, append(PropAttrs, PropElts, Properties)
}.
description(Type, About, Properties, Options) ::=
element(\name_uri(Type, Options),
\attrs([ \?idAboutAttr(About, Options)
| \propAttrs(PropAttrs, Options)
]),
\propertyElts(PropElts, Options)),
{ append(PropAttrs, PropElts, Properties)
}.
propAttrs([], _) ::=
[], !.
propAttrs([H|T], Options) ::=
[ \propAttr(H, Options)
| \propAttrs(T, Options)
].
propAttr(rdf:type = URI, Options) ::=
\rdf_or_unqualified(type) = \value_uri(URI, Options), !.
propAttr(Name = Literal, Options) ::=
Name = Value,
{ mkliteral(Value, Literal, Options)
}.
propertyElts([], _) ::=
[], !.
propertyElts(Elts, Options) ::=
[ (\ws, !)
| \propertyElts(Elts, Options)
].
propertyElts([H|T], Options) ::=
[ \propertyElt(H, Options)
| \propertyElts(T, Options)
].
propertyElt(E, Options) ::=
\propertyElt(Id, Name, Value, Options),
{ mkprop(Name, Value, Prop),
( var(Id)
-> E = Prop
; E = id(Id, Prop)
)
}.
mkprop(NS:Local, Value, rdf:Local = Value) :-
rdf_name_space(NS), !.
mkprop(Name, Value, Name = Value).
propertyElt(Id, Name, Value, Options0) ::=
E0,
{ modify_state(E0, Options0, E, Options), !,
rewrite(\propertyElt(Id, Name, Value, Options), E)
}.
propertyElt(Id, Name, Value, Options) ::=
\literalPropertyElt(Id, Name, Value, Options), !.
% 5.14 emptyPropertyElt
propertyElt(Id, Name, Value, Options) ::=
element(Name, A, \all_ws),
{ !,
rewrite(\emptyPropertyElt(Id, Value, Options), A)
}.
propertyElt(_, Name, description(description, Id, Properties), Options) ::=
element(Name,
\attrs([ \parseResource,
\?idAboutAttr(Id, Options)
]),
\propertyElts(Properties, Options)),
!.
propertyElt(_, Name, Literal, Options) ::=
element(Name,
\attrs([ \parseLiteral
]),
Content),
{ !,
literal_value(Content, Literal, Options)
}.
propertyElt(Id, Name, collection(Elements), Options) ::=
element(Name,
\attrs([ \parseCollection,
\?idAttr(Id, Options)
]),
\nodeElementList(Elements, Options)).
propertyElt(Id, Name, Literal, Options) ::=
element(Name,
\attrs([ \?idAttr(Id, Options)
]),
[ Value ]),
{ atom(Value), !,
mkliteral(Value, Literal, Options)
}.
propertyElt(Id, Name, Value, Options) ::=
element(Name,
\attrs([ \?idAttr(Id, Options)
]),
\an_rdf_object(Value, Options)), !.
propertyElt(Id, Name, unparsed(Value), Options) ::=
element(Name,
\attrs([ \?idAttr(Id, Options)
]),
Value).
literalPropertyElt(Id, Name, Literal, Options) ::=
element(Name,
\attrs([ \typeAttr(Type, Options),
\?idAttr(Id, Options)
]),
Content),
{ typed_literal(Type, Content, Literal, Options)
}.
emptyPropertyElt(Id, Literal, Options) ::=
\attrs([ \?idAttr(Id, Options),
\?parseLiteral
| \noMoreAttrs
]),
{ !,
mkliteral('', Literal, Options)
}.
emptyPropertyElt(Id,
description(description, About, Properties),
Options) ::=
\attrs([ \?idAttr(Id, Options),
\?aboutResourceEmptyElt(About, Options),
\?parseResource
| \propAttrs(Properties, Options)
]), !.
aboutResourceEmptyElt(about(URI), Options) ::=
\resourceAttr(URI, Options), !.
aboutResourceEmptyElt(node(URI), _Options) ::=
\nodeIDAttr(URI).
%% literal_value(+In, -Value, +Options)
%
% Create the literal value for rdf:parseType="Literal" attributes.
% The content is the Prolog XML DOM tree for the literal.
%
% @tbd Note that the specs demand a canonical textual representation
% of the XML data as a Unicode string. For now the user can
% achieve this using the convert_typed_literal hook.
literal_value(Value, literal(type(rdf:'XMLLiteral', Value)), _).
%% mkliteral(+Atom, -Object, +Options)
%
% Translate attribute value Atom into an RDF object using the
% lang(Lang) option from Options.
mkliteral(Text, literal(Val), Options) :-
atom(Text),
( rdf_state_lang(Options, Lang),
Lang \== ''
-> Val = lang(Lang, Text)
; Val = Text
).
%% typed_literal(+Type, +Content, -Literal, +Options)
%
% Handle a literal attribute with rdf:datatype=Type qualifier. NB:
% possibly it is faster to use a global variable for the
% conversion hook.
typed_literal(Type, Content, literal(Object), Options) :-
rdf_state_convert_typed_literal(Options, Convert),
nonvar(Convert), !,
( catch(call(Convert, Type, Content, Object), E, true)
-> ( var(E)
-> true
; Object = E
)
; Object = error(cannot_convert(Type, Content), _)
).
typed_literal(Type, [], literal(type(Type, '')), _Options) :- !.
typed_literal(Type, [Text], literal(type(Type, Text)), _Options) :- !.
typed_literal(Type, Content, literal(type(Type, Content)), _Options).
idAboutAttr(id(Id), Options) ::=
\idAttr(Id, Options), !.
idAboutAttr(about(About), Options) ::=
\aboutAttr(About, Options), !.
idAboutAttr(node(About), _Options) ::=
\nodeIDAttr(About), !.
%% an_rdf_object(-Object, +OptionsURI)
%
% Deals with an object, but there may be spaces around. I'm still
% not sure where to deal with these. Best is to ask the XML parser
% to get rid of them, So most likely this code will change if this
% happens.
an_rdf_object(Object, Options) ::=
[ \nodeElement(Object, Options)
], !.
an_rdf_object(Object, Options) ::=
[ (\ws, !)
| \an_rdf_object(Object, Options)
].
an_rdf_object(Object, Options) ::=
[ \nodeElement(Object, Options),
\ws
], !.
ws ::=
A,
{ atom(A),
atom_chars(A, Chars),
all_blank(Chars), !
}.
ws ::=
pi(_).
all_ws ::=
[], !.
all_ws ::=
[\ws | \all_ws].
all_blank([]).
all_blank([H|T]) :-
char_type(H, space), % SWI-Prolog specific
all_blank(T).
/*******************************
* RDF ATTRIBUTES *
*******************************/
idAttr(Id, Options) ::=
\rdf_or_unqualified('ID') = \uniqueid(Id, Options).
aboutAttr(About, Options) ::=
\rdf_or_unqualified(about) = \value_uri(About, Options).
nodeIDAttr(About) ::=
\rdf_or_unqualified(nodeID) = About.
resourceAttr(URI, Options) ::=
\rdf_or_unqualified(resource) = \value_uri(URI, Options).
typeAttr(Type, Options) ::=
\rdf_or_unqualified(datatype) = \value_uri(Type, Options).
name_uri(URI, Options) ::=
NS:Local,
{ !, atom_concat(NS, Local, A),
rewrite(\value_uri(URI, Options), A)
}.
name_uri(URI, Options) ::=
\value_uri(URI, Options).
value_uri(URI, Options) ::=
A,
{ rdf_state_base_uri(Options, Base),
uri_normalized_iri(A, Base, URI)
}.
globalid(Id, Options) ::=
A,
{ make_globalid(A, Options, Id)
}.
uniqueid(Id, Options) ::=
A,
{ unique_xml_name(A, HashID),
make_globalid(HashID, Options, Id)
}.
unique_xml_name(Name, HashID) :-
atom_concat(#, Name, HashID),
( xml_name(Name)
-> true
; print_message(warning, rdf(not_a_name(Name)))
).
make_globalid(In, Options, Id) :-
rdf_state_base_uri(Options, Base),
uri_normalized_iri(In, Base, Id).
parseLiteral ::= \rdf_or_unqualified(parseType) = 'Literal'.
parseResource ::= \rdf_or_unqualified(parseType) = 'Resource'.
parseCollection ::= \rdf_or_unqualified(parseType) = 'Collection'.
/*******************************
* PRIMITIVES *
*******************************/
rdf(Tag) ::=
NS:Tag,
{ rdf_name_space(NS), !
}.
rdf_or_unqualified(Tag) ::=
Tag.
rdf_or_unqualified(Tag) ::=
NS:Tag,
{ rdf_name_space(NS), !
}.
/*******************************
* BASICS *
*******************************/
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
This code is translated by the goal_expansion/2 rule at the start of
this file. We leave the original code for reference.
attrs(Bag) ::=
L0,
{ do_attrs(Bag, L0)
}.
do_attrs([], _) :- !.
do_attrs([\?H|T], L0) :- !, % optional
( select(X, L0, L),
rewrite(\H, X)
-> true
; L = L0
),
do_attrs(T, L).
do_attrs([H|T], L0) :-
select(X, L0, L),
rewrite(H, X), !,
do_attrs(T, L).
do_attrs(C, L) :-
rewrite(C, L).
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
% \noMoreAttrs
%
% Check attribute-list is empty. Reserved xml: attributes are
% excluded from this test.
noMoreAttrs ::=
[], !.
noMoreAttrs ::=
[ xml:_=_
| \noMoreAttrs
].
%% modify_state(+Element0, +Options0, -Element, -Options) is semidet.
%
% If Element0 contains xml:base = Base, strip it from the
% attributes list and update base_uri(_) in the Options
%
% It Element0 contains xml:lang = Lang, strip it from the
% attributes list and update lang(_) in the Options
%
% Remove all xmlns=_, xmlns:_=_ and xml:_=_. Only succeed
% if something changed.
modify_state(element(Name, Attrs0, Content), Options0,
element(Name, Attrs, Content), Options) :-
modify_a_state(Attrs0, Options0, Attrs, Options),
Attrs0 \== Attrs.
rdf_modify_state(Attributes, State0, State) :-
modify_a_state(Attributes, State0, _, State).
modify_a_state([], Options, [], Options).
modify_a_state([Name=Value|T0], Options0, T, Options) :-
modify_a(Name, Value, Options0, Options1), !,
modify_a_state(T0, Options1, T, Options).
modify_a_state([H|T0], Options0, [H|T], Options) :-
modify_a_state(T0, Options0, T, Options).
modify_a(xml:base, Base1, Options0, Options) :- !,
rdf_state_base_uri(Options0, Base0),
remove_fragment(Base1, Base2),
uri_normalized_iri(Base2, Base0, Base),
set_base_uri_of_rdf_state(Base, Options0, Options).
modify_a(xml:lang, Lang, Options0, Options) :- !,
rdf_state_ignore_lang(Options0, false), !,
set_lang_of_rdf_state(Lang, Options0, Options).
modify_a(xmlns, _, Options, Options).
modify_a(xmlns:_, _, Options, Options).
modify_a(xml:_, _, Options, Options).
%% remove_fragment(+URI, -WithoutFragment)
%
% When handling xml:base, we must delete the possible fragment.
remove_fragment(URI, Plain) :-
sub_atom(URI, B, _, _, #), !,
sub_atom(URI, 0, B, _, Plain).
remove_fragment(URI, URI).
/*******************************
* HELP PCE-EMACS A BIT *
*******************************/
:- multifile
emacs_prolog_colours:term_colours/2,
emacs_prolog_colours:goal_classification/2.
expand(c(X), _, X) :- !.
expand(In, Pattern, Colours) :-
compound(In), !,
In =.. [F|Args],
expand_list(Args, PatternArgs, ColourArgs),
Pattern =.. [F|PatternArgs],
Colours = functor(F) - ColourArgs.
expand(X, X, classify).
expand_list([], [], []).
expand_list([H|T], [PH|PT], [CH|CT]) :-
expand(H, PH, CH),
expand_list(T, PT, CT).
:- discontiguous
term_expansion/2.
term_expansion(term_colours(C),
emacs_prolog_colours:term_colours(Pattern, Colours)) :-
expand(C, Pattern, Colours).
term_colours((c(head(+(1))) ::= c(match), {c(body)})).
term_colours((c(head(+(1))) ::= c(match))).
emacs_prolog_colours:goal_classification(\_, expanded).
:- dynamic
prolog:meta_goal/2.
:- multifile
prolog:meta_goal/2,
prolog:called_by/2.
prolog:meta_goal(rewrite(A, _), [A]).
prolog:meta_goal(\A, [A+1]).
prolog:called_by(attrs(Attrs, _Term), Called) :-
findall(G+1, sub_term(\?G, Attrs), Called, Tail),
findall(G+1, sub_term(\G, Attrs), Tail).

414
packages/RDF/rdf_triple.pl Normal file
View File

@ -0,0 +1,414 @@
/* Part of SWI-Prolog
Author: Jan Wielemaker
E-mail: J.Wielemaker@uva.nl
WWW: http://www.swi-prolog.org
Copyright (C): 2002-2010, University of Amsterdam
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
as published by the Free Software Foundation; either version 2
of the License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
As a special exception, if you link this library with other files,
compiled with a Free Software compiler, to produce an executable, this
library does not by itself cause the resulting executable to be covered
by the GNU General Public License. This exception does not however
invalidate any other reasons why the executable file might be covered by
the GNU General Public License.
*/
:- module(rdf_triple,
[ rdf_triples/2, % +Parsed, -Tripples
rdf_triples/3, % +Parsed, -Tripples, +Tail
rdf_reset_ids/0, % Reset gensym id's
rdf_start_file/2, % +Options, -Cleanup
rdf_end_file/1, % +Cleanup
anon_prefix/1 % Prefix for anonynmous resources
]).
:- use_module(library(gensym)).
:- use_module(rdf_parser).
/** <module> Create triples from intermediate representation
Convert the output of xml_to_rdf/3 from library(rdf) into a list of
triples of the format described below. The intermediate representation
should be regarded a proprietary representation.
rdf(Subject, Predicate, Object).
Where `Subject' is
* Atom
The subject is a resource
* each(URI)
URI is the URI of an RDF Bag
* prefix(Pattern)
Pattern is the prefix of a fully qualified Subject URI
And `Predicate' is
* Atom
The predicate is always a resource
And `Object' is
* Atom
URI of Object resource
* literal(Value)
Literal value (Either a single atom or parsed XML data)
*/
%% rdf_triples(+Term, -Triples) is det.
%% rdf_triples(+Term, -Tridpples, +Tail) is det.
%
% Convert an object as parsed by rdf.pl into a list of rdf/3
% triples. The identifier of the main object created is returned
% by rdf_triples/3.
%
% Input is the `content' of the RDF element in the format as
% generated by load_structure(File, Term, [dialect(xmlns)]).
% rdf_triples/3 can process both individual descriptions as
% well as the entire content-list of an RDF element. The first
% mode is suitable when using library(sgml) in `call-back' mode.
rdf_triples(RDF, Tripples) :-
rdf_triples(RDF, Tripples, []).
rdf_triples([]) --> !,
[].
rdf_triples([H|T]) --> !,
rdf_triples(H),
rdf_triples(T).
rdf_triples(Term) -->
triples(Term, _).
%% triples(-Triples, -Id, +In, -Tail)
%
% DGC set processing the output of xml_to_rdf/3. Id is unified to
% the identifier of the main description.
triples(description(Type, About, Props), Subject) -->
{ var(About),
share_blank_nodes(true)
}, !,
( { shared_description(description(Type, Props), Subject)
}
-> []
; { make_id('__Description', Id)
},
triples(description(Type, about(Id), Props), Subject),
{ assert_shared_description(description(Type, Props), Subject)
}
).
triples(description(description, IdAbout, Props), Subject) --> !,
{ description_id(IdAbout, Subject)
},
properties(Props, Subject).
triples(description(TypeURI, IdAbout, Props), Subject) -->
{ description_id(IdAbout, Subject)
},
properties([ rdf:type = TypeURI
| Props
], Subject).
triples(unparsed(Data), Id) -->
{ make_id('__Error', Id),
print_message(error, rdf(unparsed(Data)))
},
[].
/*******************************
* DESCRIPTIONS *
*******************************/
:- thread_local
node_id/2, % nodeID --> ID
unique_id/1. % known rdf:ID
rdf_reset_node_ids :-
retractall(node_id(_,_)),
retractall(unique_id(_)).
description_id(Id, Id) :-
var(Id), !,
make_id('__Description', Id).
description_id(about(Id), Id).
description_id(id(Id), Id) :-
( unique_id(Id)
-> print_message(error, rdf(redefined_id(Id)))
; assert(unique_id(Id))
).
description_id(each(Id), each(Id)).
description_id(prefix(Id), prefix(Id)).
description_id(node(NodeID), Id) :-
( node_id(NodeID, Id)
-> true
; make_id('__Node', Id),
assert(node_id(NodeID, Id))
).
properties(PlRDF, Subject) -->
properties(PlRDF, 1, [], [], Subject).
properties([], _, Bag, Bag, _) -->
[].
properties([H0|T0], N, Bag0, Bag, Subject) -->
property(H0, N, NN, Bag0, Bag1, Subject),
properties(T0, NN, Bag1, Bag, Subject).
%% property(Property, N, NN, Subject)// is det.
%
% Generate triples for {Subject, Pred, Object}. Also generates
% triples for Object if necessary.
%
% @param Property One of
%
% * Pred = Object
% Used for normal statements
% * id(Id, Pred = Object)
% Used for reified statements
property(Pred0 = Object, N, NN, BagH, BagT, Subject) --> % inlined object
triples(Object, Id), !,
{ li_pred(Pred0, Pred, N, NN)
},
statement(Subject, Pred, Id, _, BagH, BagT).
property(Pred0 = collection(Elems), N, NN, BagH, BagT, Subject) --> !,
{ li_pred(Pred0, Pred, N, NN)
},
statement(Subject, Pred, Object, _Id, BagH, BagT),
collection(Elems, Object).
property(Pred0 = Object, N, NN, BagH, BagT, Subject) --> !,
{ li_pred(Pred0, Pred, N, NN)
},
statement(Subject, Pred, Object, _Id, BagH, BagT).
property(id(Id, Pred0 = Object), N, NN, BagH, BagT, Subject) -->
triples(Object, ObjectId), !,
{ li_pred(Pred0, Pred, N, NN)
},
statement(Subject, Pred, ObjectId, Id, BagH, BagT).
property(id(Id, Pred0 = collection(Elems)), N, NN, BagH, BagT, Subject) --> !,
{ li_pred(Pred0, Pred, N, NN)
},
statement(Subject, Pred, Object, Id, BagH, BagT),
collection(Elems, Object).
property(id(Id, Pred0 = Object), N, NN, BagH, BagT, Subject) -->
{ li_pred(Pred0, Pred, N, NN)
},
statement(Subject, Pred, Object, Id, BagH, BagT).
%% statement(+Subject, +Pred, +Object, +Id, +BagH, -BagT)
%
% Add a statement to the model. If nonvar(Id), we reinify the
% statement using the given Id.
statement(Subject, Pred, Object, Id, BagH, BagT) -->
rdf(Subject, Pred, Object),
{ BagH = [Id|BagT]
-> statement_id(Id)
; BagT = BagH
},
( { nonvar(Id)
}
-> rdf(Id, rdf:type, rdf:'Statement'),
rdf(Id, rdf:subject, Subject),
rdf(Id, rdf:predicate, Pred),
rdf(Id, rdf:object, Object)
; []
).
statement_id(Id) :-
nonvar(Id), !.
statement_id(Id) :-
make_id('__Statement', Id).
%% li_pred(+Pred, -Pred, +Nth, -NextNth)
%
% Transform rdf:li predicates into _1, _2, etc.
li_pred(rdf:li, rdf:Pred, N, NN) :- !,
NN is N + 1,
atom_concat('_', N, Pred).
li_pred(Pred, Pred, N, N).
%% collection(+Elems, -Id)
%
% Handle the elements of a collection and return the identifier
% for the whole collection in Id.
collection([], Nil) -->
{ global_ref(rdf:nil, Nil)
}.
collection([H|T], Id) -->
triples(H, HId),
{ make_id('__List', Id)
},
rdf(Id, rdf:type, rdf:'List'),
rdf(Id, rdf:first, HId),
rdf(Id, rdf:rest, TId),
collection(T, TId).
rdf(S0, P0, O0) -->
{ global_ref(S0, S),
global_ref(P0, P),
global_obj(O0, O)
},
[ rdf(S, P, O) ].
global_ref(In, Out) :-
( nonvar(In),
In = NS:Local
-> ( NS == rdf,
rdf_name_space(RDF)
-> atom_concat(RDF, Local, Out)
; atom_concat(NS, Local, Out)
)
; Out = In
).
global_obj(V, V) :-
var(V), !.
global_obj(literal(type(Local, X)), literal(type(Global, X))) :- !,
global_ref(Local, Global).
global_obj(literal(X), literal(X)) :- !.
global_obj(Local, Global) :-
global_ref(Local, Global).
/*******************************
* SHARING *
*******************************/
:- thread_local
shared_description/3, % +Hash, +Term, -Subject
share_blank_nodes/1, % Boolean
shared_nodes/1. % counter
reset_shared_descriptions :-
retractall(shared_description(_,_,_)),
retractall(shared_nodes(_)).
shared_description(Term, Subject) :-
term_hash(Term, Hash),
shared_description(Hash, Term, Subject),
( retract(shared_nodes(N))
-> N1 is N + 1
; N1 = 1
),
assert(shared_nodes(N1)).
assert_shared_description(Term, Subject) :-
term_hash(Term, Hash),
assert(shared_description(Hash, Term, Subject)).
/*******************************
* START/END *
*******************************/
%% rdf_start_file(+Options, -Cleanup) is det.
%
% Initialise for the translation of a file.
rdf_start_file(Options, Cleanup) :-
rdf_reset_node_ids, % play safe
reset_shared_descriptions,
set_bnode_sharing(Options, C1),
set_anon_prefix(Options, C2),
add_cleanup(C1, C2, Cleanup).
%% rdf_end_file(:Cleanup) is det.
%
% Cleanup reaching the end of an RDF file.
rdf_end_file(Cleanup) :-
rdf_reset_node_ids,
( shared_nodes(N)
-> print_message(informational, rdf(shared_blank_nodes(N)))
; true
),
reset_shared_descriptions,
Cleanup.
set_bnode_sharing(Options, erase(Ref)) :-
option(blank_nodes(Share), Options, noshare),
( Share == share
-> assert(share_blank_nodes(true), Ref), !
; Share == noshare
-> fail % next clause
; throw(error(domain_error(share, Share), _))
).
set_bnode_sharing(_, true).
set_anon_prefix(Options, erase(Ref)) :-
option(base_uri(BaseURI), Options),
nonvar(BaseURI), !,
atomic_list_concat(['__', BaseURI, '#'], AnonBase),
asserta(anon_prefix(AnonBase), Ref).
set_anon_prefix(_, true).
add_cleanup(true, X, X) :- !.
add_cleanup(X, true, X) :- !.
add_cleanup(X, Y, (X, Y)).
/*******************************
* UTIL *
*******************************/
%% anon_prefix(-Prefix) is semidet.
%
% If defined, it is the prefix used to generate a blank node.
:- thread_local
anon_prefix/1.
make_id(For, ID) :-
anon_prefix(Prefix), !,
atom_concat(Prefix, For, Base),
gensym(Base, ID).
make_id(For, ID) :-
gensym(For, ID).
anon_base('__Description').
anon_base('__Statement').
anon_base('__List').
anon_base('__Node').
%% rdf_reset_ids is det.
%
% Utility predicate to reset the gensym counters for the various
% generated identifiers. This simplifies debugging and matching
% output with the stored desired output (see rdf_test.pl).
rdf_reset_ids :-
anon_prefix(Prefix), !,
( anon_base(Base),
atom_concat(Prefix, Base, X),
reset_gensym(X),
fail
; true
).
rdf_reset_ids :-
( anon_base(Base),
reset_gensym(Base),
fail
; true
).

636
packages/RDF/rdf_write.pl Normal file
View File

@ -0,0 +1,636 @@
/* $Id$
Part of SWI-Prolog
Author: Jan Wielemaker
E-mail: J.Wielemak@uva.nl
WWW: http://www.swi-prolog.org
Copyright (C): 2004-2009, University of Amsterdam
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
as published by the Free Software Foundation; either version 2
of the License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU Lesser General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
As a special exception, if you link this library with other files,
compiled with a Free Software compiler, to produce an executable, this
library does not by itself cause the resulting executable to be covered
by the GNU General Public License. This exception does not however
invalidate any other reasons why the executable file might be covered by
the GNU General Public License.
*/
:- module(rdf_write,
[ rdf_write_xml/2 % +Stream, +Triples
]).
:- use_module(library('semweb/rdf_db')).
:- use_module(library(lists)).
:- use_module(library(sgml)).
:- use_module(library(sgml_write)).
:- use_module(library(assoc)).
:- use_module(library(pairs)).
:- use_module(library(debug)).
/** <module> Write RDF/XML from a list of triples
This module writes an RDF/XML document from a list of triples of the
format rdf(Subject, Predicate, Object). It is primarily intended for
communicating computed RDF model fragments to external programs using
RDF/XML.
When used from the HTTP library, use the following code:
==
reply_graph(RDF) :-
format('Content-type: application/rdf+xml; charset=UTF-8~n~n'),
rdf_write_xml(current_output, RDF).
==
@author Jan Wielemaker
@see library(semweb/rdf_db) offers saving a named graph directly from
the RDF database.
*/
/*******************************
* WRITE RDFXML *
*******************************/
%% rdf_write_xml(+Out:stream, +Triples:list(rdf(S,P,O))) is det.
%
% Write an RDF/XML serialization of Triples to Out.
rdf_write_xml(Out, Triples) :-
sort(Triples, Unique),
rdf_write_header(Out, Unique),
node_id_map(Unique, AnonIDs),
rdf_write_triples(Unique, AnonIDs, Out),
rdf_write_footer(Out).
/*******************************
* HEADER/FOOTER *
*******************************/
%% rdf_write_header(+Out, +Triples)
%
% Save XML document header, doctype and open the RDF environment.
% This predicate also sets up the namespace notation.
rdf_write_header(Out, Triples) :-
xml_encoding(Out, Enc, Encoding),
format(Out, '<?xml version=\'1.0\' encoding=\'~w\'?>~n', [Encoding]),
format(Out, '<!DOCTYPE rdf:RDF [', []),
used_namespaces(Triples, NSList),
( member(Id, NSList),
ns(Id, NS),
rdf_quote_uri(NS, QNS),
xml_quote_attribute(QNS, NSText0, Enc),
xml_escape_parameter_entity(NSText0, NSText),
format(Out, '~N <!ENTITY ~w \'~w\'>', [Id, NSText]),
fail
; true
),
format(Out, '~N]>~n~n', []),
format(Out, '<rdf:RDF', []),
( member(Id, NSList),
format(Out, '~N xmlns:~w="&~w;"~n', [Id, Id]),
fail
; true
),
format(Out, '>~n', []).
xml_encoding(Out, Enc, Encoding) :-
stream_property(Out, encoding(Enc)),
( xml_encoding_name(Enc, Encoding)
-> true
; throw(error(domain_error(rdf_encoding, Enc), _))
).
xml_encoding_name(ascii, 'US-ASCII').
xml_encoding_name(iso_latin_1, 'ISO-8859-1').
xml_encoding_name(utf8, 'UTF-8').
%% xml_escape_parameter_entity(+In, -Out) is det.
%
% Escape % as &#37; for entity declarations.
xml_escape_parameter_entity(In, Out) :-
sub_atom(In, _, _, _, '%'), !,
atom_codes(In, Codes),
phrase(escape_parent(Codes), OutCodes),
atom_codes(Out, OutCodes).
xml_escape_parameter_entity(In, In).
escape_parent([]) --> [].
escape_parent([H|T]) -->
( { H == 37 }
-> "&#37;"
; [H]
),
escape_parent(T).
%% used_namespaces(+Triples:list(rdf(S,P,O)), -List:atom) is det.
%
% Return the list of namespace abbreviations used in a set of
% triples.
used_namespaces(Triples, NSList) :-
decl_used_predicate_ns(Triples),
resources(Triples, Resources),
empty_assoc(A0),
put_assoc(rdf, A0, *, A1), % needed for rdf:RDF
res_used_namespaces(Resources, _NoNS, A1, A),
assoc_to_keys(A, NSList).
res_used_namespaces([], [], A, A).
res_used_namespaces([Resource|T], NoNS, A0, A) :-
ns(NS, Full),
Full \== '',
atom_concat(Full, _Local, Resource), !,
put_assoc(NS, A0, *, A1),
res_used_namespaces(T, NoNS, A1, A).
res_used_namespaces([R|T0], [R|T], A0, A) :-
res_used_namespaces(T0, T, A0, A).
%% resources(+Triples:list(rdf(S,P,O)), -Resources:list(atom)) is det.
%
% Resources is the set of resources referenced in Triples.
resources(Triples, Resources) :-
phrase(resources(Triples), Raw),
sort(Raw, Resources).
resources([]) -->
[].
resources([rdf(S,P,O)|T]) -->
[S,P],
object_resources(O),
resources(T).
object_resources(Atom) -->
{ atom(Atom) }, !,
[ Atom ].
object_resources(literal(type(Type, _))) --> !,
[ Type ].
object_resources(_) -->
[].
%% decl_used_predicate_ns(+Triples:list(rdf(S,P,O)))
%
% For every URL used as a predicate we *MUST* define a namespace
% as we cannot use names holding /, :, etc. as XML identifiers.
:- thread_local
predicate_ns/2.
decl_used_predicate_ns(Triples) :-
retractall(predicate_ns(_,_)),
( member(rdf(_,P,_), Triples),
decl_predicate_ns(P),
fail
; true
).
decl_predicate_ns(Pred) :-
predicate_ns(Pred, _), !.
decl_predicate_ns(Pred) :-
rdf_global_id(NS:_Local, Pred),
assert(predicate_ns(Pred, NS)), !.
decl_predicate_ns(Pred) :-
is_bag_li_predicate(Pred), !.
decl_predicate_ns(Pred) :-
atom_codes(Pred, Codes),
append(NSCodes, LocalCodes, Codes),
xml_codes(LocalCodes), !,
( NSCodes \== []
-> atom_codes(NS, NSCodes),
( ns(Id, NS)
-> assert(predicate_ns(Pred, Id))
; between(1, infinite, N),
atom_concat(ns, N, Id),
\+ ns(Id, _)
-> rdf_register_ns(Id, NS),
print_message(informational,
rdf(using_namespace(Id, NS)))
),
assert(predicate_ns(Pred, Id))
; assert(predicate_ns(Pred, -)) % no namespace used
).
xml_codes([]).
xml_codes([H|T]) :-
xml_code(H),
xml_codes(T).
xml_code(X) :-
code_type(X, csym), !.
xml_code(0'-). % '
rdf_write_footer(Out) :-
format(Out, '</rdf:RDF>~n', []).
/*******************************
* ANONYMOUS IDS *
*******************************/
%% node_id_map(+Triples, -IdMap) is det.
%
% Create an assoc Resource -> NodeID for those anonymous resources
% in Triples that need a NodeID. This implies all anonymous
% resources that are used multiple times as object value.
node_id_map(Triples, IdMap) :-
anonymous_objects(Triples, Objs),
msort(Objs, Sorted),
empty_assoc(IdMap0),
nodeid_map(Sorted, 0, IdMap0, IdMap).
anonymous_objects([], []).
anonymous_objects([rdf(_,_,O)|T0], Anon) :-
rdf_is_bnode(O), !,
Anon = [O|T],
anonymous_objects(T0, T).
anonymous_objects([_|T0], T) :-
anonymous_objects(T0, T).
nodeid_map([], _, Map, Map).
nodeid_map([H,H|T0], Id, Map0, Map) :- !,
remove_leading(H, T0, T),
atom_concat(bn, Id, NodeId),
put_assoc(H, Map0, NodeId, Map1),
Id2 is Id + 1,
nodeid_map(T, Id2, Map1, Map).
nodeid_map([_|T], Id, Map0, Map) :-
nodeid_map(T, Id, Map0, Map).
remove_leading(H, [H|T0], T) :- !,
remove_leading(H, T0, T).
remove_leading(_, T, T).
/*******************************
* TRIPLES *
*******************************/
rdf_write_triples(Triples, NodeIDs, Out) :-
rdf_write_triples(Triples, NodeIDs, Out, [], Anon),
rdf_write_anon(Anon, NodeIDs, Out, Anon).
rdf_write_triples([], _, _, Anon, Anon).
rdf_write_triples([H|T0], NodeIDs, Out, Anon0, Anon) :-
arg(1, H, S),
subject_triples(S, [H|T0], T, OnSubject),
( rdf_is_bnode(S)
-> rdf_write_triples(T, NodeIDs, Out, [anon(S,_,OnSubject)|Anon0], Anon)
; rdf_write_subject(OnSubject, S, NodeIDs, Out, Anon0),
rdf_write_triples(T, NodeIDs, Out, Anon0, Anon)
).
subject_triples(S, [H|T0], T, [H|M]) :-
arg(1, H, S), !,
subject_triples(S, T0, T, M).
subject_triples(_, T, T, []).
rdf_write_anon([], _, _, _).
rdf_write_anon([anon(Subject, Done, Triples)|T], NodeIDs, Out, Anon) :-
Done \== true, !,
Done = true,
rdf_write_subject(Triples, Subject, NodeIDs, Out, Anon),
rdf_write_anon(T, NodeIDs, Out, Anon).
rdf_write_anon([_|T], NodeIDs, Out, Anon) :-
rdf_write_anon(T, NodeIDs, Out, Anon).
rdf_write_subject(Triples, Subject, NodeIDs, Out, Anon) :-
rdf_write_subject(Triples, Out, Subject, NodeIDs, -, 0, Anon), !,
format(Out, '~n', []).
rdf_write_subject(_, Subject, _, _, _) :-
throw(error(rdf_save_failed(Subject), 'Internal error')).
rdf_write_subject(Triples, Out, Subject, NodeIDs, DefNS, Indent, Anon) :-
rdf_equal(rdf:type, RdfType),
select(rdf(_, RdfType,Type), Triples, Triples1),
\+ rdf_is_bnode(Type),
rdf_id(Type, DefNS, TypeId),
xml_is_name(TypeId), !,
format(Out, '~*|<', [Indent]),
rdf_write_id(Out, TypeId),
save_about(Out, Subject, NodeIDs),
save_attributes(Triples1, DefNS, Out, NodeIDs, TypeId, Indent, Anon).
rdf_write_subject(Triples, Out, Subject, NodeIDs, _DefNS, Indent, Anon) :-
format(Out, '~*|<rdf:Description', [Indent]),
save_about(Out, Subject, NodeIDs),
save_attributes(Triples, rdf, Out, NodeIDs, rdf:'Description', Indent, Anon).
xml_is_name(_NS:Atom) :- !,
xml_name(Atom).
xml_is_name(Atom) :-
xml_name(Atom).
save_about(Out, Subject, NodeIDs) :-
rdf_is_bnode(Subject), !,
( get_assoc(Subject, NodeIDs, NodeID)
-> format(Out,' rdf:nodeID="~w"', [NodeID])
; true
).
save_about(Out, Subject, _) :-
stream_property(Out, encoding(Encoding)),
rdf_value(Subject, QSubject, Encoding),
format(Out, ' rdf:about="~w"', [QSubject]), !.
save_about(_, _, _) :-
assertion(fail).
%% save_attributes(+List, +DefNS, +Out, +NodeIDs, Element, +Indent, +Anon)
%
% Save the attributes. Short literal attributes are saved in the
% tag. Others as the content of the description element. The
% begin tag has already been filled.
save_attributes(Triples, DefNS, Out, NodeIDs, Element, Indent, Anon) :-
split_attributes(Triples, InTag, InBody),
SubIndent is Indent + 2,
save_attributes2(InTag, DefNS, tag, Out, NodeIDs, SubIndent, Anon),
( InBody == []
-> format(Out, '/>~n', [])
; format(Out, '>~n', []),
save_attributes2(InBody, _, body, Out, NodeIDs, SubIndent, Anon),
format(Out, '~N~*|</~w>~n', [Indent, Element])
).
% split_attributes(+Triples, -HeadAttrs, -BodyAttr)
%
% Split attribute (Name=Value) list into attributes for the head
% and body. Attributes can only be in the head if they are literal
% and appear only one time in the attribute list.
split_attributes(Triples, HeadAttr, BodyAttr) :-
duplicate_attributes(Triples, Dupls, Singles),
simple_literal_attributes(Singles, HeadAttr, Rest),
append(Dupls, Rest, BodyAttr).
% duplicate_attributes(+Attrs, -Duplicates, -Singles)
%
% Extract attributes that appear more than onces as we cannot
% dublicate an attribute in the head according to the XML rules.
duplicate_attributes([], [], []).
duplicate_attributes([H|T], Dupls, Singles) :-
arg(2, H, Name),
named_attributes(Name, T, D, R),
D \== [],
append([H|D], Dupls2, Dupls), !,
duplicate_attributes(R, Dupls2, Singles).
duplicate_attributes([H|T], Dupls2, [H|Singles]) :-
duplicate_attributes(T, Dupls2, Singles).
named_attributes(_, [], [], []) :- !.
named_attributes(Name, [H|T], D, R) :-
( arg(2, H, Name)
-> D = [H|DT],
named_attributes(Name, T, DT, R)
; R = [H|RT],
named_attributes(Name, T, D, RT)
).
% simple_literal_attributes(+Attributes, -Inline, -Body)
%
% Split attributes for (literal) attributes to be used in the
% begin-tag and ones that have to go into the body of the description.
simple_literal_attributes([], [], []).
simple_literal_attributes([H|TA], [H|TI], B) :-
in_tag_attribute(H), !,
simple_literal_attributes(TA, TI, B).
simple_literal_attributes([H|TA], I, [H|TB]) :-
simple_literal_attributes(TA, I, TB).
in_tag_attribute(rdf(_,P,literal(Text))) :-
atom(Text), % may not have lang qualifier
atom_length(Text, Len),
Len < 60,
\+ is_bag_li_predicate(P).
% save_attributes(+List, +DefNS, +TagOrBody, +Out, +NodeIDs, +Indent, +Anon)
%
% Save a list of attributes.
save_attributes2([], _, _, _, _, _, _).
save_attributes2([H|T], DefNS, Where, Out, NodeIDs, Indent, Anon) :-
save_attribute(Where, H, DefNS, Out, NodeIDs, Indent, Anon),
save_attributes2(T, DefNS, Where, Out, NodeIDs, Indent, Anon).
%% save_attribute(+Where, +Triple, +DefNS, +Out, +NodeIDs, +Indent, +Anon)
save_attribute(tag, rdf(_, Name, literal(Value)), DefNS, Out, _, Indent, _Anon) :-
AttIndent is Indent + 2,
rdf_att_id(Name, DefNS, NameText),
stream_property(Out, encoding(Encoding)),
xml_quote_attribute(Value, QVal, Encoding),
format(Out, '~N~*|', [AttIndent]),
rdf_write_id(Out, NameText),
format(Out, '="~w"', [QVal]).
save_attribute(body, rdf(_,Name,literal(Literal)), DefNS, Out, _, Indent, _) :- !,
rdf_p_id(Name, DefNS, NameText),
format(Out, '~N~*|<', [Indent]),
rdf_write_id(Out, NameText),
( Literal = lang(Lang, Value)
-> rdf_id(Lang, DefNS, LangText),
format(Out, ' xml:lang="~w">', [LangText])
; Literal = type(Type, Value)
-> ( rdf_equal(Type, rdf:'XMLLiteral')
-> write(Out, ' rdf:parseType="Literal">'),
Value = Literal
; stream_property(Out, encoding(Encoding)),
rdf_value(Type, QVal, Encoding),
format(Out, ' rdf:datatype="~w">', [QVal])
)
; atomic(Literal)
-> write(Out, '>'),
Value = Literal
; write(Out, ' rdf:parseType="Literal">'),
Value = Literal
),
save_attribute_value(Value, Out, Indent),
write(Out, '</'), rdf_write_id(Out, NameText), write(Out, '>').
save_attribute(body, rdf(_, Name, Value), DefNS, Out, NodeIDs, Indent, Anon) :-
rdf_is_bnode(Value),
memberchk(anon(Value, Done, ValueTriples), Anon), !,
rdf_p_id(Name, DefNS, NameText),
format(Out, '~N~*|<', [Indent]),
rdf_write_id(Out, NameText),
( var(Done)
-> Done = true,
SubIndent is Indent + 2,
( rdf_equal(RdfType, rdf:type),
rdf_equal(ListClass, rdf:'List'),
memberchk(rdf(_, RdfType, ListClass), ValueTriples)
-> format(Out, ' rdf:parseType="Collection">~n', []),
rdf_save_list(ValueTriples, Out, Value, NodeIDs, DefNS, SubIndent, Anon)
; format(Out, '>~n', []),
rdf_write_subject(ValueTriples, Out, Value, NodeIDs, DefNS, SubIndent, Anon)
),
format(Out, '~N~*|</', [Indent]),
rdf_write_id(Out, NameText),
format(Out, '>~n', [])
; get_assoc(Value, NodeIDs, NodeID)
-> format(Out, ' rdf:nodeID="~w"/>', [NodeID])
; assertion(fail)
).
save_attribute(body, rdf(_, Name, Value), DefNS, Out, _, Indent, _Anon) :-
stream_property(Out, encoding(Encoding)),
rdf_value(Value, QVal, Encoding),
rdf_p_id(Name, DefNS, NameText),
format(Out, '~N~*|<', [Indent]),
rdf_write_id(Out, NameText),
format(Out, ' rdf:resource="~w"/>', [QVal]).
save_attribute_value(Value, Out, _) :- % strings
atom(Value), !,
stream_property(Out, encoding(Encoding)),
xml_quote_cdata(Value, QVal, Encoding),
write(Out, QVal).
save_attribute_value(Value, Out, _) :- % numbers
number(Value), !,
writeq(Out, Value). % quoted: preserve floats
save_attribute_value(Value, Out, Indent) :-
xml_is_dom(Value), !,
XMLIndent is Indent+2,
xml_write(Out, Value,
[ header(false),
indent(XMLIndent)
]).
save_attribute_value(Value, _Out, _) :-
throw(error(save_attribute_value(Value), _)).
rdf_save_list(_, _, List, _, _, _, _) :-
rdf_equal(List, rdf:nil), !.
rdf_save_list(ListTriples, Out, List, NodeIDs, DefNS, Indent, Anon) :-
rdf_equal(RdfFirst, rdf:first),
memberchk(rdf(List, RdfFirst, First), ListTriples),
( rdf_is_bnode(First),
memberchk(anon(First, true, FirstTriples), Anon)
-> nl(Out),
rdf_write_subject(FirstTriples, Out, First, NodeIDs, DefNS, Indent, Anon)
; stream_property(Out, encoding(Encoding)),
rdf_value(First, QVal, Encoding),
format(Out, '~N~*|<rdf:Description about="~w"/>',
[Indent, QVal])
),
( rdf_equal(RdfRest, rdf:rest),
memberchk(rdf(List, RdfRest, List2), ListTriples),
\+ rdf_equal(List2, rdf:nil),
memberchk(anon(List2, true, List2Triples), Anon)
-> rdf_save_list(List2Triples, Out, List2, NodeIDs, DefNS, Indent, Anon)
; true
).
%% rdf_p_id(+Resource, +DefNS, -NSLocal)
%
% As rdf_id/3 for predicate names. Maps _:<N> to rdf:li.
%
% @tbd Ensure we are talking about an rdf:Bag
rdf_p_id(LI, _, 'rdf:li') :-
is_bag_li_predicate(LI), !.
rdf_p_id(Resource, DefNS, NSLocal) :-
rdf_id(Resource, DefNS, NSLocal).
%% is_bag_li_predicate(+Pred) is semidet.
%
% True if Pred is _:N, as used for members of an rdf:Bag, rdf:Seq
% or rdf:Alt.
is_bag_li_predicate(Pred) :-
atom_concat('_:', AN, Pred),
catch(atom_number(AN, N), _, true), integer(N), N >= 0, !.
%% rdf_id(+Resource, +DefNS, -NSLocal)
%
% Generate a NS:Local name for Resource given the indicated
% default namespace. This call is used for elements.
rdf_id(Id, NS, NS:Local) :-
ns(NS, Full),
Full \== '',
atom_concat(Full, Local, Id), !.
rdf_id(Id, _, NS:Local) :-
ns(NS, Full),
Full \== '',
atom_concat(Full, Local, Id), !.
rdf_id(Id, _, Id).
%% rdf_write_id(+Out, +NSLocal) is det.
%
% Write an identifier. We cannot use native write on it as both NS
% and Local can be operators.
rdf_write_id(Out, NS:Local) :- !,
format(Out, '~w:~w', [NS, Local]).
rdf_write_id(Out, Atom) :-
write(Out, Atom).
rdf_att_id(Id, _, NS:Local) :-
ns(NS, Full),
Full \== '',
atom_concat(Full, Local, Id), !.
rdf_att_id(Id, _, Id).
%% rdf_value(+Resource, -Text, +Encoding)
%
% According to "6.4 RDF URI References" of the RDF Syntax
% specification, a URI reference is UNICODE string not containing
% control sequences, represented as UTF-8 and then as escaped
% US-ASCII.
%
% NOTE: the to_be_described/1 trick ensures entity rewrite in
% resources that start with 'http://t-d-b.org?'. This is a of a
% hack to save the artchive data in the MultimediaN project. We
% should use a more general mechanism.
rdf_value(V, Text, Encoding) :-
to_be_described(Prefix),
atom_concat(Prefix, V1, V),
ns(NS, Full),
atom_concat(Full, Local, V1), !,
rdf_quote_uri(Local, QLocal0),
xml_quote_attribute(QLocal0, QLocal, Encoding),
atomic_list_concat([Prefix, '&', NS, (';'), QLocal], Text).
rdf_value(V, Text, Encoding) :-
ns(NS, Full),
atom_concat(Full, Local, V), !,
rdf_quote_uri(Local, QLocal0),
xml_quote_attribute(QLocal0, QLocal, Encoding),
atomic_list_concat(['&', NS, (';'), QLocal], Text).
rdf_value(V, Q, Encoding) :-
rdf_quote_uri(V, Q0),
xml_quote_attribute(Q0, Q, Encoding).
to_be_described('http://t-d-b.org?').
/*******************************
* UTIL *
*******************************/
ns(Id, Full) :-
rdf_db:ns(Id, Full).

237
packages/RDF/rdfs.rdfs Normal file
View File

@ -0,0 +1,237 @@
<?xml version="1.0" encoding="iso-8859-1"?>
<!DOCTYPE rdf:RDF [
<!ENTITY rdfs 'http://www.w3.org/2000/01/rdf-schema#'>
<!ENTITY rdf 'http://www.w3.org/1999/02/22-rdf-syntax-ns#'>
]>
<rdf:RDF
xmlns:rdf="&rdf;"
xmlns:rdfs="&rdfs;">
<rdfs:Class rdf:about="&rdfs;Resource">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">Resource</rdfs:label>
<rdfs:comment>The class resource, everything.</rdfs:comment>
</rdfs:Class>
<rdf:Property rdf:about="&rdf;type">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">type</rdfs:label>
<rdfs:comment>Indicates membership of a class</rdfs:comment>
<rdfs:range rdf:resource="&rdfs;Class"/>
<rdfs:domain rdf:resource="&rdfs;Resource"/>
</rdf:Property>
<rdfs:Class rdf:about="&rdfs;Class">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">Class</rdfs:label>
<rdfs:comment>The concept of Class</rdfs:comment>
<rdfs:subClassOf rdf:resource="&rdfs;Resource"/>
</rdfs:Class>
<rdf:Property rdf:about="&rdfs;subClassOf">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">subClassOf</rdfs:label>
<rdfs:comment>Indicates membership of a class</rdfs:comment>
<rdfs:range rdf:resource="&rdfs;Class"/>
<rdfs:domain rdf:resource="&rdfs;Class"/>
</rdf:Property>
<rdf:Property rdf:about="&rdfs;subPropertyOf">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">subPropertyOf</rdfs:label>
<rdfs:comment>Indicates specialization of properties</rdfs:comment>
<rdfs:range rdf:resource="&rdf;Property"/>
<rdfs:domain rdf:resource="&rdf;Property"/>
</rdf:Property>
<rdfs:Class rdf:about="&rdf;Property">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">Property</rdfs:label>
<rdfs:comment>The concept of a property.</rdfs:comment>
<rdfs:subClassOf rdf:resource="&rdfs;Resource"/>
</rdfs:Class>
<rdf:Property rdf:about="&rdfs;comment">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">comment</rdfs:label>
<rdfs:comment>Use this for descriptions</rdfs:comment>
<rdfs:domain rdf:resource="&rdfs;Resource"/>
<rdfs:range rdf:resource="&rdfs;Literal"/>
</rdf:Property>
<rdf:Property rdf:about="&rdfs;label">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">label</rdfs:label>
<rdfs:comment>Provides a human-readable version of a resource name.</rdfs:comment>
<rdfs:domain rdf:resource="&rdfs;Resource"/>
<rdfs:range rdf:resource="&rdfs;Literal"/>
</rdf:Property>
<rdf:Property rdf:about="&rdfs;domain">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">domain</rdfs:label>
<rdfs:comment>A domain class for a property type</rdfs:comment>
<rdfs:range rdf:resource="&rdfs;Class"/>
<rdfs:domain rdf:resource="&rdf;Property"/>
</rdf:Property>
<rdf:Property rdf:about="&rdfs;range">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">range</rdfs:label>
<rdfs:comment>A range class for a property type</rdfs:comment>
<rdfs:range rdf:resource="&rdfs;Class"/>
<rdfs:domain rdf:resource="&rdf;Property"/>
</rdf:Property>
<rdf:Property rdf:about="&rdfs;seeAlso">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">seeAlso</rdfs:label>
<rdfs:comment>A resource that provides information about the subject resource</rdfs:comment>
<rdfs:range rdf:resource="&rdfs;Resource"/>
<rdfs:domain rdf:resource="&rdfs;Resource"/>
</rdf:Property>
<rdf:Property rdf:about="&rdfs;isDefinedBy">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdf:type resource="&rdf;Property"/>
<rdfs:subPropertyOf rdf:resource="&rdfs;seeAlso"/>
<rdfs:label xml:lang="en">isDefinedBy</rdfs:label>
<rdfs:comment>Indicates the namespace of a resource</rdfs:comment>
<rdfs:range rdf:resource="&rdfs;Resource"/>
<rdfs:domain rdf:resource="&rdfs;Resource"/>
</rdf:Property>
<rdfs:Class rdf:about="&rdfs;Literal">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">Literal</rdfs:label>
<rdfs:comment>This represents the set of atomic values, eg. textual strings.</rdfs:comment>
</rdfs:Class>
<rdfs:Class rdf:about="&rdf;Statement">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">Statement</rdfs:label>
<rdfs:subClassOf rdf:resource="&rdfs;Resource"/>
<rdfs:comment>The class of RDF statements.</rdfs:comment>
</rdfs:Class>
<rdf:Property about="&rdf;subject">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">subject</rdfs:label>
<rdfs:comment>The subject of an RDF statement.</rdfs:comment>
<rdfs:domain rdf:resource="&rdf;Statement"/>
<rdfs:range rdf:resource="&rdfs;Resource"/>
</rdf:Property>
<rdf:Property about="&rdf;predicate">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">predicate</rdfs:label>
<rdfs:comment>the predicate of an RDF statement.</rdfs:comment>
<rdfs:domain rdf:resource="&rdf;Statement"/>
<rdfs:range rdf:resource="&rdf;Property"/>
</rdf:Property>
<rdf:Property about="&rdf;object">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">object</rdfs:label>
<rdfs:comment>The object of an RDF statement.</rdfs:comment>
<rdfs:domain rdf:resource="&rdf;Statement"/>
</rdf:Property>
<rdfs:Class rdf:about="&rdfs;Container">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">Container</rdfs:label>
<rdfs:subClassOf rdf:resource="&rdfs;Resource"/>
<rdfs:comment>This represents the set Containers.</rdfs:comment>
</rdfs:Class>
<rdfs:Class rdf:about="&rdf;Bag">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">Bag</rdfs:label>
<rdfs:comment xml:lang="en">An unordered collection.</rdfs:comment>
<rdfs:subClassOf rdf:resource="&rdfs;Container"/>
</rdfs:Class>
<rdfs:Class rdf:about="&rdf;Seq">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">Seq</rdfs:label>
<rdfs:comment xml:lang="en">An ordered collection.</rdfs:comment>
<rdfs:subClassOf rdf:resource="&rdfs;Container"/>
</rdfs:Class>
<rdfs:Class rdf:about="&rdf;Alt">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">Alt</rdfs:label>
<rdfs:comment xml:lang="en">A collection of alternatives.</rdfs:comment>
<rdfs:subClassOf rdf:resource="&rdfs;Container"/>
</rdfs:Class>
<rdfs:Class rdf:about="&rdfs;ContainerMembershipProperty">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">ContainerMembershipProperty</rdfs:label>
<rdfs:comment>The container membership properties, rdf:1, rdf:2, ..., all of which are sub-properties of 'member'.</rdfs:comment>
<rdfs:subClassOf rdf:resource="&rdf;Property"/>
</rdfs:Class>
<rdf:Property rdf:about="&rdfs;member">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">member</rdfs:label>
<rdfs:comment>a member of a container</rdfs:comment>
<rdfs:domain rdf:resource="&rdfs;Container"/>
</rdf:Property>
<rdf:Property rdf:about="&rdf;value">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">value</rdfs:label>
<rdfs:comment>Identifies the principal value (usually a string) of a property when the property value is a structured resource</rdfs:comment>
<rdfs:domain rdf:resource="&rdfs;Resource"/>
</rdf:Property>
<!-- the following are new additions, Nov 2002 -->
<rdfs:Class rdf:about="&rdf;List">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">List</rdfs:label>
<rdfs:comment xml:lang="en">The class of RDF Lists</rdfs:comment>
</rdfs:Class>
<rdf:List rdf:about="&rdf;nil">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">nil</rdfs:label>
<rdfs:comment xml:lang="en">The empty list, with no items in it. If the rest of a list is nil then the list has no more items in it.</rdfs:comment>
</rdf:List>
<rdf:Property rdf:about="&rdf;first">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">first</rdfs:label>
<rdfs:comment xml:lang="en">The first item in an RDF list. Also often called the head.</rdfs:comment>
<rdfs:domain rdf:resource="&rdf;List"/>
</rdf:Property>
<rdf:Property rdf:about="&rdf;rest">
<rdfs:isDefinedBy rdf:resource="&rdf;"/>
<rdfs:label xml:lang="en">rest</rdfs:label>
<rdfs:comment xml:lang="en">The rest of an RDF list after the first item. Also often called the tail.</rdfs:comment>
<rdfs:domain rdf:resource="&rdf;List"/>
<rdfs:range rdf:resource="&rdf;List"/>
</rdf:Property>
<rdfs:Class rdf:about="&rdfs;Datatype">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">Datatype</rdfs:label>
<rdfs:comment xml:lang="en">The class of datatypes.</rdfs:comment>
</rdfs:Class>
<rdfs:Class rdf:about="&rdfs;XMLLiteral">
<rdfs:isDefinedBy rdf:resource="&rdfs;"/>
<rdfs:label xml:lang="en">XMLLiteral</rdfs:label>
<rdfs:comment>The class of XML literals.</rdfs:comment>
</rdfs:Class>
<rdf:Description rdf:about="&rdfs;">
<rdfs:seeAlso rdf:resource="http://www.w3.org/2000/01/rdf-schema-more"/>
</rdf:Description>
</rdf:RDF>

161
packages/RDF/rewrite.pl Normal file
View File

@ -0,0 +1,161 @@
/* Part of SWI-Prolog
Author: Jan Wielemaker
E-mail: J.Wielemaker@uva.nl
WWW: http://www.swi-prolog.org
Copyright (C): 2010, University of Amsterdam
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
as published by the Free Software Foundation; either version 2
of the License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
As a special exception, if you link this library with other files,
compiled with a Free Software compiler, to produce an executable, this
library does not by itself cause the resulting executable to be covered
by the GNU General Public License. This exception does not however
invalidate any other reasons why the executable file might be covered by
the GNU General Public License.
*/
:- module(rewrite,
[ rewrite/2, % +Rule, +Input
rew_term_expansion/2,
rew_goal_expansion/2,
op(1200, xfx, (::=))
]).
:- use_module(library(quintus)).
:- meta_predicate
rewrite(1, +).
/*******************************
* COMPILATION *
*******************************/
rew_term_expansion((Rule ::= RuleBody), (Head :- Body)) :-
translate(RuleBody, Term, Body0),
simplify(Body0, Body),
Rule =.. [Name|List],
Head =.. [Name,Term|List].
rew_goal_expansion(rewrite(To, From), Goal) :-
nonvar(To),
To = \Rule,
callable(Rule),
Rule =.. [Name|List],
Goal =.. [Name,From|List].
/*******************************
* TOPLEVEL *
*******************************/
%% rewrite(:To, +From)
%
% Invoke the term-rewriting system
rewrite(M:T, From) :-
( var(T)
-> From = T
; T = \Rule
-> Rule =.. [Name|List],
Goal =.. [Name,From|List],
M:Goal
; match(T, M, From)
).
match(Rule, M, From) :-
translate(Rule, From, Code),
M:Code.
translate(Var, Var, true) :-
var(Var), !.
translate((\Command, !), Var, (Goal, !)) :- !,
( callable(Command),
Command =.. [Name|List]
-> Goal =.. [Name,Var|List]
; Goal = rewrite(\Command, Var)
).
translate(\Command, Var, Goal) :- !,
( callable(Command),
Command =.. [Name|List]
-> Goal =.. [Name,Var|List]
; Goal = rewrite(\Command, Var)
).
translate(Atomic, Atomic, true) :-
atomic(Atomic), !.
translate(C, _, Cmd) :-
command(C, Cmd), !.
translate((A, B), T, Code) :-
( command(A, Cmd)
-> !, translate(B, T, C),
Code = (Cmd, C)
; command(B, Cmd)
-> !, translate(A, T, C),
Code = (C, Cmd)
).
translate(Term0, Term, Command) :-
functor(Term0, Name, Arity),
functor(Term, Name, Arity),
translate_args(0, Arity, Term0, Term, Command).
translate_args(N, N, _, _, true) :- !.
translate_args(I0, Arity, T0, T1, (C0,C)) :-
I is I0 + 1,
arg(I, T0, A0),
arg(I, T1, A1),
translate(A0, A1, C0),
translate_args(I, Arity, T0, T1, C).
command(0, _) :- !, % catch variables
fail.
command({A}, A).
command(!, !).
/*******************************
* SIMPLIFY *
*******************************/
%% simplify(+Raw, -Simplified)
%
% Get rid of redundant `true' goals generated by translate/3.
simplify(V, V) :-
var(V), !.
simplify((A0,B), A) :-
B == true, !,
simplify(A0, A).
simplify((A,B0), B) :-
A == true, !,
simplify(B0, B).
simplify((A0, B0), C) :- !,
simplify(A0, A),
simplify(B0, B),
( ( A \== A0
; B \== B0
)
-> simplify((A,B), C)
; C = (A,B)
).
simplify(X, X).
/*******************************
* XREF *
*******************************/
:- multifile
prolog:called_by/2.
prolog:called_by(rewrite(Spec, _Term), Called) :-
findall(G+1, sub_term(\G, Spec), Called).

View File

@ -0,0 +1,12 @@
<?xml version="1.0"?>
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:ex="http://example.org/stuff/1.0/">
<rdf:Description rdf:about="http://example.org/basket">
<ex:hasFruit rdf:ID="l1" rdf:parseType="Collection">
<rdf:Description rdf:about="http://example.org/banana"/>
<rdf:Description rdf:about="http://example.org/apple"/>
<rdf:Description rdf:about="http://example.org/pear"/>
</ex:hasFruit>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,14 @@
rdf('http://example.org/basket', 'http://example.org/stuff/1.0/hasFruit', '__List1').
rdf('#l1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement').
rdf('#l1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#subject', 'http://example.org/basket').
rdf('#l1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#predicate', 'http://example.org/stuff/1.0/hasFruit').
rdf('#l1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#object', '__List1').
rdf('__List1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#List').
rdf('__List1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#first', 'http://example.org/banana').
rdf('__List1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#rest', '__List2').
rdf('__List2', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#List').
rdf('__List2', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#first', 'http://example.org/apple').
rdf('__List2', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#rest', '__List3').
rdf('__List3', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#List').
rdf('__List3', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#first', 'http://example.org/pear').
rdf('__List3', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#rest', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#nil').

View File

@ -0,0 +1 @@
rdf('http://www.w3.org/Home/Lassila', 'http://description.org/schema/':'Creator', literal('Ora Lassila')).

View File

@ -0,0 +1 @@
rdf('http://www.swi.psy.uva.nl/projects/SWI-Prolog/', 'http://description.org/schema/':'Creator', literal('Jan Wielemaker')).

View File

@ -0,0 +1 @@
rdf('http://www.w3.org/Home/Lassila', 'http://description.org/schema/':'Creator', literal('Ora Lassila')).

View File

@ -0,0 +1 @@
rdf('http://www.w3.org/Home/Lassila', 'http://description.org/schema/':'Creator', literal('Ora Lassila')).

View File

@ -0,0 +1,3 @@
rdf('http://www.w3.org', 'http://description.org/schema/Publisher', literal('World Wide Web Consortium')).
rdf('http://www.w3.org', 'http://description.org/schema/Title', literal('W3C Home Page')).
rdf('http://www.w3.org', 'http://description.org/schema/Date', literal('1998-10-03T02:27')).

View File

@ -0,0 +1,3 @@
rdf('http://www.w3.org', 'http://description.org/schema/Publisher', literal('World Wide Web Consortium')).
rdf('http://www.w3.org', 'http://description.org/schema/Title', literal('W3C Home Page')).
rdf('http://www.w3.org', 'http://description.org/schema/Date', literal('1998-10-03T02:27')).

View File

@ -0,0 +1,3 @@
rdf('http://www.w3.org/Home/Lassila', 'http://description.org/schema/':'Creator', 'http://www.w3.org/staffId/85740').
rdf('http://www.w3.org/staffId/85740', 'http://description.org/schema/':'Name', literal('Ora Lassila')).
rdf('http://www.w3.org/staffId/85740', 'http://description.org/schema/':'Email', literal('lassila@w3.org')).

View File

@ -0,0 +1,3 @@
rdf('http://www.w3.org/staffId/85740', 'http://description.org/schema/':'Name', literal('Ora Lassila')).
rdf('http://www.w3.org/staffId/85740', 'http://description.org/schema/':'Email', literal('lassila@w3.org')).
rdf('http://www.w3.org/Home/Lassila', 'http://description.org/schema/':'Creator', 'http://www.w3.org/staffId/85740').

View File

@ -0,0 +1,3 @@
rdf('http://www.w3.org/staffId/85740', 'http://description.org/schema/':'Name', literal('Ora Lassila')).
rdf('http://www.w3.org/staffId/85740', 'http://description.org/schema/':'Email', literal('lassila@w3.org')).
rdf('http://www.w3.org/Home/Lassila', 'http://description.org/schema/':'Creator', 'http://www.w3.org/staffId/85740').

View File

@ -0,0 +1,4 @@
rdf('http://www.w3.org/staffId/85740', rdf:type, 'http://description.org/schema/Person').
rdf('http://www.w3.org/staffId/85740', 'http://description.org/view/':'Name', literal('Ora Lassila')).
rdf('http://www.w3.org/staffId/85740', 'http://description.org/view/':'Email', literal('lassila@w3.org')).
rdf('http://www.w3.org/Home/Lassila', 'http://description.org/schema/':'Creator', 'http://www.w3.org/staffId/85740').

View File

@ -0,0 +1,3 @@
rdf('JW', sex, literal(male)).
rdf('JW', employed_at, literal('SWI')).
rdf('SWI-prolog', 'http://description.org/schema/':'Creator', 'JW').

View File

@ -0,0 +1,4 @@
rdf('http://www.w3.org/staffId/85740', rdf:type, 'http://description.org/schema/Person').
rdf('http://www.w3.org/staffId/85740', 'http://description.org/view/':'Name', literal('Ora Lassila')).
rdf('http://www.w3.org/staffId/85740', 'http://description.org/view/':'Email', literal('lassila@w3.org')).
rdf('http://www.w3.org/Home/Lassila', 'http://description.org/schema/':'Creator', 'http://www.w3.org/staffId/85740').

View File

@ -0,0 +1,7 @@
rdf('__Bag1', rdf:type, rdf:'Bag').
rdf('__Bag1', rdf:'_1', 'http://mycollege.edu/students/Amy').
rdf('__Bag1', rdf:'_2', 'http://mycollege.edu/students/Tim').
rdf('__Bag1', rdf:'_3', 'http://mycollege.edu/students/John').
rdf('__Bag1', rdf:'_4', 'http://mycollege.edu/students/Mary').
rdf('__Bag1', rdf:'_5', 'http://mycollege.edu/students/Sue').
rdf('http://mycollege.edu/courses/6.001', 'http://description.org/schema/':students, '__Bag1').

View File

@ -0,0 +1,5 @@
rdf('__Alt1', rdf:type, rdf:'Alt').
rdf('__Alt1', rdf:'_1', 'ftp://ftp.x.org').
rdf('__Alt1', rdf:'_2', 'ftp://ftp.cs.purdue.edu').
rdf('__Alt1', rdf:'_3', 'ftp://ftp.eu.net').
rdf('http://x.org/packages/X11', 'http://description.org/schema/':'DistributionSite', '__Alt1').

View File

@ -0,0 +1,5 @@
rdf('__Description1', rdf:subject, 'http://www.w3.org/Home/Lassila').
rdf('__Description1', rdf:predicate, 'http://description.org/schema/Creator').
rdf('__Description1', rdf:object, literal('Ora Lassila')).
rdf('__Description1', rdf:type, 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement').
rdf('__Description1', 'http://description.org/schema/':attributedTo, literal('Ralph Swick')).

View File

@ -0,0 +1,8 @@
rdf('#JSPapersByDate', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Seq').
rdf('#JSPapersByDate', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_1', 'http://www.dogworld.com/Aug96.doc').
rdf('#JSPapersByDate', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_2', 'http://www.webnuts.net/Jan97.html').
rdf('#JSPapersByDate', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_3', 'http://www.carchat.com/Sept97.html').
rdf('#JSPapersBySubj', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Seq').
rdf('#JSPapersBySubj', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_1', 'http://www.carchat.com/Sept97.html').
rdf('#JSPapersBySubj', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_2', 'http://www.dogworld.com/Aug96.doc').
rdf('#JSPapersBySubj', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_3', 'http://www.webnuts.net/Jan97.html').

View File

@ -0,0 +1,12 @@
rdf('#CreatorsAlphabeticalBySurname', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Seq').
rdf('#CreatorsAlphabeticalBySurname', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_1', literal('Mary Andrew')).
rdf('#CreatorsAlphabeticalBySurname', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_2', literal('Jacky Crystal')).
rdf('http://www.foo.com/cool.html', 'http://purl.org/metadata/dublin_core#Creator', '#CreatorsAlphabeticalBySurname').
rdf('#MirroredSites', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Bag').
rdf('#MirroredSites', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_1', 'http://www.foo.com.au/cool.html').
rdf('#MirroredSites', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_2', 'http://www.foo.com.it/cool.html').
rdf('http://www.foo.com/cool.html', 'http://purl.org/metadata/dublin_core#Identifier', '#MirroredSites').
rdf('__Description1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Alt').
rdf('__Description1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_1', literal(lang(en, 'The Coolest Web Page'))).
rdf('__Description1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_2', literal(lang(it, 'Il Pagio di Web Fuba'))).
rdf('http://www.foo.com/cool.html', 'http://purl.org/metadata/dublin_core#Title', '__Description1').

View File

@ -0,0 +1,3 @@
rdf('__Description1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#':value, literal('020 - Library Science')).
rdf('__Description1', 'http://mycorp.com/schemas/my-schema#':'Classification', literal('Dewey Decimal Code')).
rdf('http://www.webnuts.net/Jan97.html', 'http://purl.org/metadata/dublin_core#':'Subject', '__Description1').

View File

@ -0,0 +1,3 @@
rdf('__Description1', rdf:value, literal('200')).
rdf('__Description1', 'http://www.nist.gov/units/':units, 'http://www.nist.gov/units/Pounds').
rdf('John_Smith', 'http://www.nist.gov/units/':weight, '__Description1').

View File

@ -0,0 +1,3 @@
rdf('#JW', 'http://description.org/schema/name', literal('Jan Wielemaker')).
rdf('#JW', 'http://description.org/schema/works_at', literal('SWI')).
rdf('http://www.swi.psy.uva.nl/projects/SWI-Prolog/', 'http://description.org/schema/Creator', '#JW').

View File

@ -0,0 +1,12 @@
rdf('http://www.dlib.org', 'http://purl.org/metadata/dublin_core#Title', literal('D-Lib Program - Research in Digital Libraries')).
rdf('http://www.dlib.org', 'http://purl.org/metadata/dublin_core#Description', literal('The D-Lib program supports the community of people\n with research interests in digital libraries and electronic\n publishing.')).
rdf('http://www.dlib.org', 'http://purl.org/metadata/dublin_core#Publisher', literal('Corporation For National Research Initiatives')).
rdf('http://www.dlib.org', 'http://purl.org/metadata/dublin_core#Date', literal('1995-01-07')).
rdf('__Bag1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Bag').
rdf('__Bag1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_1', literal('Research; statistical methods')).
rdf('__Bag1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_2', literal('Education, research, related topics')).
rdf('__Bag1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_3', literal('Library use Studies')).
rdf('http://www.dlib.org', 'http://purl.org/metadata/dublin_core#Subject', '__Bag1').
rdf('http://www.dlib.org', 'http://purl.org/metadata/dublin_core#Type', literal('World Wide Web Home Page')).
rdf('http://www.dlib.org', 'http://purl.org/metadata/dublin_core#Format', literal('text/html')).
rdf('http://www.dlib.org', 'http://purl.org/metadata/dublin_core#Language', literal(en)).

View File

@ -0,0 +1,17 @@
rdf('http://www.dlib.org/dlib/may98/05contents.html', 'http://purl.org/metadata/dublin_core#Title', literal('DLIB Magazine - The Magazine for Digital Library Research\n - May 1998')).
rdf('http://www.dlib.org/dlib/may98/05contents.html', 'http://purl.org/metadata/dublin_core#Description', literal('D-LIB magazine is a monthly compilation of\n contributed stories, commentary, and briefings.')).
rdf('__Description1', 'http://purl.org/metadata/dublin_core_qualifiers#AgentType', 'http://purl.org/metadata/dublin_core_qualifiers#Editor').
rdf('__Description1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#value', literal('Amy Friedlander')).
rdf('http://www.dlib.org/dlib/may98/05contents.html', 'http://purl.org/metadata/dublin_core#Contributor', '__Description1').
rdf('http://www.dlib.org/dlib/may98/05contents.html', 'http://purl.org/metadata/dublin_core#Publisher', literal('Corporation for National Research Initiatives')).
rdf('http://www.dlib.org/dlib/may98/05contents.html', 'http://purl.org/metadata/dublin_core#Date', literal('1998-01-05')).
rdf('http://www.dlib.org/dlib/may98/05contents.html', 'http://purl.org/metadata/dublin_core#Type', literal('electronic journal')).
rdf('__Bag1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Bag').
rdf('__Bag1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_1', literal('library use studies')).
rdf('__Bag1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_2', literal('magazines and newspapers')).
rdf('http://www.dlib.org/dlib/may98/05contents.html', 'http://purl.org/metadata/dublin_core#Subject', '__Bag1').
rdf('http://www.dlib.org/dlib/may98/05contents.html', 'http://purl.org/metadata/dublin_core#Format', literal('text/html')).
rdf('http://www.dlib.org/dlib/may98/05contents.html', 'http://purl.org/metadata/dublin_core#Identifier', literal('urn:issn:1082-9873')).
rdf('__Description2', 'http://purl.org/metadata/dublin_core_qualifiers#RelationType', 'http://purl.org/metadata/dublin_core_qualifiers#IsPartOf').
rdf('__Description2', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#value', 'http://www.dlib.org').
rdf('http://www.dlib.org/dlib/may98/05contents.html', 'http://purl.org/metadata/dublin_core#Relation', '__Description2').

View File

@ -0,0 +1,15 @@
rdf('http://www.dlib.org/dlib/may98/miller/05miller.html', 'http://purl.org/metadata/dublin_core#':'Title', literal('An Introduction to the Resource Description Framework')).
rdf('http://www.dlib.org/dlib/may98/miller/05miller.html', 'http://purl.org/metadata/dublin_core#':'Creator', literal('Eric J. Miller')).
rdf('http://www.dlib.org/dlib/may98/miller/05miller.html', 'http://purl.org/metadata/dublin_core#':'Description', literal('The Resource Description Framework (RDF) is an\n infrastructure that enables the encoding, exchange and reuse of\n structured metadata. rdf is an application of xml that imposes needed\n structural constraints to provide unambiguous methods of expressing\n semantics. rdf additionally provides a means for publishing both\n human-readable and machine-processable vocabularies designed to\n encourage the reuse and extension of metadata semantics among\n disparate information communities. the structural constraints rdf\n imposes to support the consistent encoding and exchange of\n standardized metadata provides for the interchangeability of separate\n packages of metadata defined by different resource description\n communities. ')).
rdf('http://www.dlib.org/dlib/may98/miller/05miller.html', 'http://purl.org/metadata/dublin_core#':'Publisher', literal('Corporation for National Research Initiatives')).
rdf('__Bag1', rdf:type, rdf:'Bag').
rdf('__Bag1', rdf:'_1', literal('machine-readable catalog record formats')).
rdf('__Bag1', rdf:'_2', literal('applications of computer file organization and\n\t access methods')).
rdf('http://www.dlib.org/dlib/may98/miller/05miller.html', 'http://purl.org/metadata/dublin_core#':'Subject', '__Bag1').
rdf('http://www.dlib.org/dlib/may98/miller/05miller.html', 'http://purl.org/metadata/dublin_core#':'Rights', literal('Copyright @ 1998 Eric Miller')).
rdf('http://www.dlib.org/dlib/may98/miller/05miller.html', 'http://purl.org/metadata/dublin_core#':'Type', literal('Electronic Document')).
rdf('http://www.dlib.org/dlib/may98/miller/05miller.html', 'http://purl.org/metadata/dublin_core#':'Format', literal('text/html')).
rdf('http://www.dlib.org/dlib/may98/miller/05miller.html', 'http://purl.org/metadata/dublin_core#':'Language', literal(en)).
rdf('__Description1', 'http://purl.org/metadata/dublin_core_qualifiers#':'RelationType', 'http://purl.org/metadata/dublin_core_qualifiers#IsPartOf').
rdf('__Description1', rdf:value, 'http://www.dlib.org/dlib/may98/05contents.html').
rdf('http://www.dlib.org/dlib/may98/miller/05miller.html', 'http://purl.org/metadata/dublin_core#':'Relation', '__Description1').

View File

@ -0,0 +1,2 @@
rdf('http://mycorp.com/papers/NobelPaper1', 'http://purl.org/metadata/dublin_core#Title', literal(type('http://www.w3.org/1999/02/22-rdf-syntax-ns#XMLLiteral', ['Ramifications of ', element('http://www.w3.org/TR/REC-mathml':apply, [], [element('http://www.w3.org/TR/REC-mathml':power, [], []), element('http://www.w3.org/TR/REC-mathml':apply, [], [element('http://www.w3.org/TR/REC-mathml':plus, [], []), element('http://www.w3.org/TR/REC-mathml':ci, [], [a]), element('http://www.w3.org/TR/REC-mathml':ci, [], [b])]), element('http://www.w3.org/TR/REC-mathml':cn, [], ['2'])]), ' to World Peace\n ']))).
rdf('http://mycorp.com/papers/NobelPaper1', 'http://purl.org/metadata/dublin_core#Creator', literal('David Hume')).

View File

@ -0,0 +1,4 @@
rdf('#CreatorsAlphabeticalBySurname', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Seq').
rdf('#CreatorsAlphabeticalBySurname', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_1', literal('Mary Andrew')).
rdf('#CreatorsAlphabeticalBySurname', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#_2', literal('Jacky Crystal')).
rdf('http://www.foo.com/cool.html', 'http://purl.org/metadata/dublin_core#Creator', '#CreatorsAlphabeticalBySurname').

View File

@ -0,0 +1,7 @@
rdf('JW', 'http://description.org/schema/name', literal('Jan Wielemaker')).
rdf('JW', 'http://description.org/schema/works_at', literal('SWI')).
rdf('http://www.swi.psy.uva.nl/projects/SWI-Prolog/', 'http://description.org/schema/Creator', 'JW').
rdf('#pl-creator', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement').
rdf('#pl-creator', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#subject', 'http://www.swi.psy.uva.nl/projects/SWI-Prolog/').
rdf('#pl-creator', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#predicate', 'http://description.org/schema/Creator').
rdf('#pl-creator', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#object', 'JW').

View File

@ -0,0 +1,128 @@
rdf('#Resource', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('#Resource', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'Resource'))).
rdf('#Resource', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, 'Ressource'))).
rdf('#Resource', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('The most general class')).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, type))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, type))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('Indicates membership of a class')).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#range', '#Class').
rdf('#comment', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('#comment', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, comment))).
rdf('#comment', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, commentaire))).
rdf('#comment', 'http://www.w3.org/2000/01/rdf-schema#domain', '#Resource').
rdf('#comment', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('Use this for descriptions')).
rdf('#comment', 'http://www.w3.org/2000/01/rdf-schema#range', '#Literal').
rdf('#label', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('#label', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('#label', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, label))).
rdf('#label', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, label))).
rdf('#label', 'http://www.w3.org/2000/01/rdf-schema#domain', '#Resource').
rdf('#label', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('Provides a human-readable version of a resource name.')).
rdf('#label', 'http://www.w3.org/2000/01/rdf-schema#range', '#Literal').
rdf('#Class', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('#Class', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'Class'))).
rdf('#Class', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, 'Classe'))).
rdf('#Class', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('The concept of Class')).
rdf('#Class', 'http://www.w3.org/2000/01/rdf-schema#subClassOf', '#Resource').
rdf('#subClassOf', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('#subClassOf', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, subClassOf))).
rdf('#subClassOf', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, sousClasseDe))).
rdf('#subClassOf', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('Indicates membership of a class')).
rdf('#subClassOf', 'http://www.w3.org/2000/01/rdf-schema#range', '#Class').
rdf('#subClassOf', 'http://www.w3.org/2000/01/rdf-schema#domain', '#Class').
rdf('#subPropertyOf', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('#subPropertyOf', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, subPropertyOf))).
rdf('#subPropertyOf', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, sousPropriétéDe))).
rdf('#subPropertyOf', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('Indicates specialization of properties')).
rdf('#subPropertyOf', 'http://www.w3.org/2000/01/rdf-schema#range', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('#subPropertyOf', 'http://www.w3.org/2000/01/rdf-schema#domain', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('#seeAlso', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('#seeAlso', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, seeAlso))).
rdf('#seeAlso', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, voirAussi))).
rdf('#seeAlso', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('Indicates a resource that provides information about the subject resource.')).
rdf('#seeAlso', 'http://www.w3.org/2000/01/rdf-schema#range', 'http://www.w3.org/2000/01/rdf-schema#Resource').
rdf('#seeAlso', 'http://www.w3.org/2000/01/rdf-schema#domain', 'http://www.w3.org/2000/01/rdf-schema#Resource').
rdf('#isDefinedBy', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('#isDefinedBy', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('#isDefinedBy', 'http://www.w3.org/2000/01/rdf-schema#subPropertyOf', '#seeAlso').
rdf('#isDefinedBy', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, isDefinedBy))).
rdf('#isDefinedBy', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, esDéfiniPar))).
rdf('#isDefinedBy', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('Indicates a resource containing and defining the subject resource.')).
rdf('#isDefinedBy', 'http://www.w3.org/2000/01/rdf-schema#range', 'http://www.w3.org/2000/01/rdf-schema#Resource').
rdf('#isDefinedBy', 'http://www.w3.org/2000/01/rdf-schema#domain', 'http://www.w3.org/2000/01/rdf-schema#Resource').
rdf('#ConstraintResource', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('#ConstraintResource', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'ConstraintResource'))).
rdf('#ConstraintResource', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, 'RessourceContrainte'))).
rdf('#ConstraintResource', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', '#Class').
rdf('#ConstraintResource', 'http://www.w3.org/2000/01/rdf-schema#subClassOf', '#Resource').
rdf('#ConstraintResource', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('Resources used to express RDF Schema constraints.')).
rdf('#ConstraintProperty', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('#ConstraintProperty', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'ConstraintProperty'))).
rdf('#ConstraintProperty', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, 'PropriétéContrainte'))).
rdf('#ConstraintProperty', 'http://www.w3.org/2000/01/rdf-schema#subClassOf', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('#ConstraintProperty', 'http://www.w3.org/2000/01/rdf-schema#subClassOf', '#ConstraintResource').
rdf('#ConstraintProperty', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('Properties used to express RDF Schema constraints.')).
rdf('#domain', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#ConstraintProperty').
rdf('#domain', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, domain))).
rdf('#domain', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, domaine))).
rdf('#domain', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('This is how we associate a class with\n properties that its instances can have')).
rdf('#range', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#ConstraintProperty').
rdf('#range', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, range))).
rdf('#range', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, étendue))).
rdf('#range', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('Properties that can be used in a\n schema to provide constraints')).
rdf('#range', 'http://www.w3.org/2000/01/rdf-schema#range', '#Class').
rdf('#range', 'http://www.w3.org/2000/01/rdf-schema#domain', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Property', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Property', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'Property'))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Property', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, 'Propriété'))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Property', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('The concept of a property.')).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Property', 'http://www.w3.org/2000/01/rdf-schema#subClassOf', '#Resource').
rdf('#Literal', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('#Literal', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'Literal'))).
rdf('#Literal', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, 'Littéral'))).
rdf('#Literal', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', '#Class').
rdf('#Literal', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('This represents the set of atomic values, eg. textual strings.')).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'Statement'))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, 'Déclaration'))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement', 'http://www.w3.org/2000/01/rdf-schema#subClassOf', '#Resource').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('This represents the set of reified statements.')).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#subject', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#subject', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, subject))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#subject', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, sujet))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#subject', 'http://www.w3.org/2000/01/rdf-schema#domain', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#subject', 'http://www.w3.org/2000/01/rdf-schema#range', '#Resource').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#predicate', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#predicate', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, predicate))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#predicate', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, prédicat))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#predicate', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#predicate', 'http://www.w3.org/2000/01/rdf-schema#domain', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#predicate', 'http://www.w3.org/2000/01/rdf-schema#range', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#object', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#object', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, object))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#object', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, objet))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#object', 'http://www.w3.org/2000/01/rdf-schema#domain', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement').
rdf('#Container', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('#Container', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'Container'))).
rdf('#Container', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, 'Enveloppe'))).
rdf('#Container', 'http://www.w3.org/2000/01/rdf-schema#subClassOf', '#Resource').
rdf('#Container', 'http://www.w3.org/2000/01/rdf-schema#comment', literal('This represents the set Containers.')).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Bag', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Bag', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'Bag'))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Bag', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, 'Ensemble'))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Bag', 'http://www.w3.org/2000/01/rdf-schema#subClassOf', '#Container').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Seq', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Seq', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'Sequence'))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Seq', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, 'Séquence'))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Seq', 'http://www.w3.org/2000/01/rdf-schema#subClassOf', '#Container').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Alt', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Alt', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'Alt'))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Alt', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, 'Choix'))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#Alt', 'http://www.w3.org/2000/01/rdf-schema#subClassOf', '#Container').
rdf('#ContainerMembershipProperty', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2000/01/rdf-schema#Class').
rdf('#ContainerMembershipProperty', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, 'ContainerMembershipProperty'))).
rdf('#ContainerMembershipProperty', 'http://www.w3.org/2000/01/rdf-schema#subClassOf', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#value', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property').
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#value', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(en, object))).
rdf('http://www.w3.org/1999/02/22-rdf-syntax-ns#value', 'http://www.w3.org/2000/01/rdf-schema#label', literal(lang(fr, value))).

View File

@ -0,0 +1,9 @@
rdf('#OntologyObjectMetaClass', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/TR/1999/PR-rdf-schema-19990303#Class').
rdf('#OntologyObjectMetaClass', 'http://www.w3.org/TR/1999/PR-rdf-schema-19990303#subClassOf', 'http://www.w3.org/TR/1999/PR-rdf-schema-19990303#Class').
rdf('#OntologyObjectMetaClass', 'http://smi-web.stanford.edu/projects/protege/protege-rdf/protege-19992012#abstractProperty', literal(concrete)).
rdf('#identifier', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/TR/1999/PR-rdf-schema-19990303#Property').
rdf('__Description1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/rdfutil#facetResource').
rdf('__Description1', 'http://www.w3.org/rdfutil#domain', '#OntologyObjectMetaClass').
rdf('__Description1', 'http://www.w3.org/rdfutil#range', 'http://www.w3.org/TR/xmlschema-2/#string').
rdf('__Description1', 'http://www.w3.org/rdfutil#cardinality', literal('1')).
rdf('#identifier', 'http://www.w3.org/rdfutil#facets', '__Description1').

View File

@ -0,0 +1,6 @@
rdf('http://www.w3.org/Home/Lassila', 'http://description.org/schema/Creator', literal('Ora Lassila')).
rdf('#statement1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement').
rdf('#statement1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#subject', 'http://www.w3.org/Home/Lassila').
rdf('#statement1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#predicate', 'http://description.org/schema/Creator').
rdf('#statement1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#object', literal('Ora Lassila')).
rdf('#statement1', 'http://description.org/schema/believedBy', literal('Stefan Decker')).

View File

@ -0,0 +1,4 @@
rdf('__Description1', rdf:type, 'http://www.mytypes.org/schema/Bicycle').
rdf('__Description1', wheels, literal('2')).
rdf('__Description2', rdf:type, 'http://www.mytypes.org/schema/Bicycle').
rdf('__Description2', 'http://www.mytypes.org/schema/':wheels, literal('2')).

View File

@ -0,0 +1,3 @@
rdf('#JohnWeight', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#value', literal('200')).
rdf('#JohnWeight', 'http://www.nist.gov/units/units', 'http://www.nist.gov/units/Pounds').
rdf('John_Smith', 'http://www.nist.gov/units/weight', '#JohnWeight').

View File

@ -0,0 +1,4 @@
rdf('John_Smith', a1, literal('John')).
rdf('__Description1', v, literal('200')).
rdf('__Description1', t, literal(pounds)).
rdf('John_Smith', a1, '__Description1').

View File

@ -0,0 +1,7 @@
rdf('__Description1', name, literal('Jan Wielemaker')).
rdf('__Description1', works_at, literal('SWI')).
rdf('http://www.swi.psy.uva.nl/projects/SWI-Prolog/', 'http://description.org/schema/Creator', '__Description1').
rdf('#JW', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement').
rdf('#JW', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#subject', 'http://www.swi.psy.uva.nl/projects/SWI-Prolog/').
rdf('#JW', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#predicate', 'http://description.org/schema/Creator').
rdf('#JW', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#object', '__Description1').

View File

@ -0,0 +1,4 @@
rdf('__Bag1', rdf:type, rdf:'Bag').
rdf('__Bag1', rdf:'_1', literal('Jan Wielemaker')).
rdf('__Bag1', rdf:'_2', literal('Anjo Anjewierden')).
rdf('http://www.swi.psy.uva.nl/projects/xpce/', 'http://description.org/schema/':'Creator', '__Bag1').

View File

@ -0,0 +1,5 @@
rdf('__Bag1', rdf:type, rdf:'Bag').
rdf('__Description1', name, literal('Jan Wielemaker')).
rdf('__Description1', employed_at, literal('SWI')).
rdf('__Bag1', rdf:'_1', '__Description1').
rdf('http://www.swi.psy.uva.nl/projects/xpce/', 'http://description.org/schema/':'Creator', '__Bag1').

View File

@ -0,0 +1,3 @@
rdf('#weight_001', 'http://www.nist.gov/RDFschema/Units', 'http://www.nist.gov/units/pounds').
rdf('#weight_001', value, literal('200')).
rdf('John_Smith', 'http://www.nist.gov/RDFschema/Weight', '#weight_001').

View File

@ -0,0 +1,6 @@
rdf('__Description1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2002/07/owl#Restriction').
rdf('http://www.w3.org/2002/03owlt/I5.8/inconsistent001#p', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.w3.org/2002/07/owl#DatatypeProperty').
rdf('http://www.w3.org/2002/03owlt/I5.8/inconsistent001#p', 'http://www.w3.org/2000/01/rdf-schema#range', 'http://www.w3.org/2001/XMLSchema#byte').
rdf('__Description1', 'http://www.w3.org/2002/07/owl#onProperty', 'http://www.w3.org/2002/03owlt/I5.8/inconsistent001#p').
rdf('__Description1', 'http://www.w3.org/2002/07/owl#cardinality', literal(type('http://www.w3.org/2001/XMLSchema#nonNegativeInteger', '257'))).
rdf('http://www.w3.org/2002/03owlt/I5.8/inconsistent001#john', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', '__Description1').

View File

@ -0,0 +1,2 @@
rdf('#id1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.swi.psy.uva.nl/test#test').
rdf('#id1', 'http://www.swi.psy.uva.nl/test#a', literal(type('http://www.w3.org/1999/02/22-rdf-syntax-ns#XMLLiteral', [element(b, [], [strong])]))).

View File

@ -0,0 +1,2 @@
rdf('#id1', 'http://www.w3.org/1999/02/22-rdf-syntax-ns#type', 'http://www.swi.psy.uva.nl/test#test').
rdf('#id1', 'http://www.swi.psy.uva.nl/test#int', literal(type('http://www.w3.org/2000/10/XMLSchema#int', '42'))).

10
packages/RDF/suite/t1.rdf Normal file
View File

@ -0,0 +1,10 @@
<?xml version='1.0'?>
<!-- Example 1 from REC-rdf-syntax -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.w3.org/Home/Lassila">
<s:Creator>Ora Lassila</s:Creator>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,7 @@
<?xml version='1.0'?>
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.swi.psy.uva.nl/projects/SWI-Prolog/"
s:Creator="Jan Wielemaker"/>
</rdf:RDF>

View File

@ -0,0 +1,11 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating namespaces -->
<RDF
xmlns="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<Description about="http://www.w3.org/Home/Lassila">
<s:Creator>Ora Lassila</s:Creator>
</Description>
</RDF>

View File

@ -0,0 +1,9 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating namespaces -->
<RDF xmlns="http://www.w3.org/1999/02/22-rdf-syntax-ns#">
<Description about="http://www.w3.org/Home/Lassila">
<Creator xmlns="http://description.org/schema/">Ora Lassila</Creator>
</Description>
</RDF>

View File

@ -0,0 +1,12 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.w3.org">
<s:Publisher>World Wide Web Consortium</s:Publisher>
<s:Title>W3C Home Page</s:Title>
<s:Date>1998-10-03T02:27</s:Date>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,11 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.w3.org"
s:Publisher="World Wide Web Consortium"
s:Title="W3C Home Page"
s:Date="1998-10-03T02:27"/>
</rdf:RDF>

View File

@ -0,0 +1,15 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.w3.org/Home/Lassila">
<s:Creator rdf:resource="http://www.w3.org/staffId/85740"/>
</rdf:Description>
<rdf:Description about="http://www.w3.org/staffId/85740">
<s:Name>Ora Lassila</s:Name>
<s:Email>lassila@w3.org</s:Email>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,15 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.w3.org/Home/Lassila">
<s:Creator>
<rdf:Description about="http://www.w3.org/staffId/85740">
<s:Name>Ora Lassila</s:Name>
<s:Email>lassila@w3.org</s:Email>
</rdf:Description>
</s:Creator>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,12 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.w3.org/Home/Lassila">
<s:Creator rdf:resource="http://www.w3.org/staffId/85740"
s:Name="Ora Lassila"
s:Email="lassila@w3.org"/>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,17 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/"
xmlns:v="http://description.org/view/">
<rdf:Description about="http://www.w3.org/Home/Lassila">
<s:Creator>
<rdf:Description about="http://www.w3.org/staffId/85740">
<rdf:type resource="http://description.org/schema/Person"/>
<v:Name>Ora Lassila</v:Name>
<v:Email>lassila@w3.org</v:Email>
</rdf:Description>
</s:Creator>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,8 @@
<?xml version='1.0'?>
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="SWI-prolog">
<s:Creator rdf:resource="JW" sex="male" employed_at="SWI"/>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,17 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/"
xmlns:v="http://description.org/view/">
<rdf:Description about="http://www.w3.org/Home/Lassila">
<s:Creator>
<!-- REC-rdf-syntax just says `about' -->
<s:Person rdf:about="http://www.w3.org/staffId/85740">
<v:Name>Ora Lassila</v:Name>
<v:Email>lassila@w3.org</v:Email>
</s:Person>
</s:Creator>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,19 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/"
xmlns:v="http://description.org/view/">
<rdf:Description about="http://mycollege.edu/courses/6.001">
<s:students>
<rdf:Bag>
<rdf:li resource="http://mycollege.edu/students/Amy"/>
<rdf:li resource="http://mycollege.edu/students/Tim"/>
<rdf:li resource="http://mycollege.edu/students/John"/>
<rdf:li resource="http://mycollege.edu/students/Mary"/>
<rdf:li resource="http://mycollege.edu/students/Sue"/>
</rdf:Bag>
</s:students>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,17 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/"
xmlns:v="http://description.org/view/">
<rdf:Description about="http://x.org/packages/X11">
<s:DistributionSite>
<rdf:Alt>
<rdf:li resource="ftp://ftp.x.org"/>
<rdf:li resource="ftp://ftp.cs.purdue.edu"/>
<rdf:li resource="ftp://ftp.eu.net"/>
</rdf:Alt>
</s:DistributionSite>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,15 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:a="http://description.org/schema/">
<rdf:Description>
<rdf:subject resource="http://www.w3.org/Home/Lassila" />
<rdf:predicate resource="http://description.org/schema/Creator" />
<rdf:object>Ora Lassila</rdf:object>
<rdf:type resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement" />
<a:attributedTo>Ralph Swick</a:attributedTo>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,16 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<RDF xmlns="http://www.w3.org/1999/02/22-rdf-syntax-ns#">
<Seq ID="JSPapersByDate">
<li resource="http://www.dogworld.com/Aug96.doc"/>
<li resource="http://www.webnuts.net/Jan97.html"/>
<li resource="http://www.carchat.com/Sept97.html"/>
</Seq>
<Seq ID="JSPapersBySubj">
<li resource="http://www.carchat.com/Sept97.html"/>
<li resource="http://www.dogworld.com/Aug96.doc"/>
<li resource="http://www.webnuts.net/Jan97.html"/>
</Seq>
</RDF>

View File

@ -0,0 +1,30 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:dc="http://purl.org/metadata/dublin_core#">
<rdf:Description about="http://www.foo.com/cool.html">
<dc:Creator>
<rdf:Seq ID="CreatorsAlphabeticalBySurname">
<rdf:li>Mary Andrew</rdf:li>
<rdf:li>Jacky Crystal</rdf:li>
</rdf:Seq>
</dc:Creator>
<dc:Identifier>
<rdf:Bag ID="MirroredSites">
<rdf:li rdf:resource="http://www.foo.com.au/cool.html"/>
<rdf:li rdf:resource="http://www.foo.com.it/cool.html"/>
</rdf:Bag>
</dc:Identifier>
<dc:Title>
<rdf:Alt>
<rdf:li xml:lang="en">The Coolest Web Page</rdf:li>
<rdf:li xml:lang="it">Il Pagio di Web Fuba</rdf:li>
</rdf:Alt>
</dc:Title>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,15 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<RDF
xmlns="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:dc="http://purl.org/metadata/dublin_core#"
xmlns:l="http://mycorp.com/schemas/my-schema#">
<Description about="http://www.webnuts.net/Jan97.html">
<dc:Subject
rdf:value="020 - Library Science"
l:Classification="Dewey Decimal Code"/>
</Description>
</RDF>

View File

@ -0,0 +1,15 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<RDF
xmlns="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:n="http://www.nist.gov/units/">
<Description about="John_Smith">
<n:weight rdf:parseType="Resource">
<rdf:value>200</rdf:value>
<n:units rdf:resource="http://www.nist.gov/units/Pounds"/>
</n:weight>
</Description>
</RDF>

15
packages/RDF/suite/t3.rdf Normal file
View File

@ -0,0 +1,15 @@
<?xml version='1.0'?>
<!-- Test inline description -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.swi.psy.uva.nl/projects/SWI-Prolog/">
<s:Creator>
<rdf:Description ID="JW">
<s:name>Jan Wielemaker</s:name>
<s:works_at>SWI</s:works_at>
</rdf:Description>
</s:Creator>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,26 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:dc="http://purl.org/metadata/dublin_core#">
<rdf:Description about="http://www.dlib.org">
<dc:Title>D-Lib Program - Research in Digital Libraries</dc:Title>
<dc:Description>The D-Lib program supports the community of people
with research interests in digital libraries and electronic
publishing.</dc:Description>
<dc:Publisher>Corporation For National Research Initiatives</dc:Publisher>
<dc:Date>1995-01-07</dc:Date>
<dc:Subject>
<rdf:Bag>
<rdf:li>Research; statistical methods</rdf:li>
<rdf:li>Education, research, related topics</rdf:li>
<rdf:li>Library use Studies</rdf:li>
</rdf:Bag>
</dc:Subject>
<dc:Type>World Wide Web Home Page</dc:Type>
<dc:Format>text/html</dc:Format>
<dc:Language>en</dc:Language>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,36 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:dc="http://purl.org/metadata/dublin_core#"
xmlns:dcq="http://purl.org/metadata/dublin_core_qualifiers#">
<rdf:Description about="http://www.dlib.org/dlib/may98/05contents.html">
<dc:Title>DLIB Magazine - The Magazine for Digital Library Research
- May 1998</dc:Title>
<dc:Description>D-LIB magazine is a monthly compilation of
contributed stories, commentary, and briefings.</dc:Description>
<dc:Contributor rdf:parseType="Resource">
<dcq:AgentType
rdf:resource="http://purl.org/metadata/dublin_core_qualifiers#Editor"/>
<rdf:value>Amy Friedlander</rdf:value>
</dc:Contributor>
<dc:Publisher>Corporation for National Research Initiatives</dc:Publisher>
<dc:Date>1998-01-05</dc:Date>
<dc:Type>electronic journal</dc:Type>
<dc:Subject>
<rdf:Bag>
<rdf:li>library use studies</rdf:li>
<rdf:li>magazines and newspapers</rdf:li>
</rdf:Bag>
</dc:Subject>
<dc:Format>text/html</dc:Format>
<dc:Identifier>urn:issn:1082-9873</dc:Identifier>
<dc:Relation rdf:parseType="Resource">
<dcq:RelationType
rdf:resource="http://purl.org/metadata/dublin_core_qualifiers#IsPartOf"/>
<rdf:value resource="http://www.dlib.org"/>
</dc:Relation>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,43 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<rdf:RDF
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:dc="http://purl.org/metadata/dublin_core#"
xmlns:dcq="http://purl.org/metadata/dublin_core_qualifiers#">
<rdf:Description about=
"http://www.dlib.org/dlib/may98/miller/05miller.html">
<dc:Title>An Introduction to the Resource Description Framework</dc:Title>
<dc:Creator>Eric J. Miller</dc:Creator>
<dc:Description>The Resource Description Framework (RDF) is an
infrastructure that enables the encoding, exchange and reuse of
structured metadata. rdf is an application of xml that imposes needed
structural constraints to provide unambiguous methods of expressing
semantics. rdf additionally provides a means for publishing both
human-readable and machine-processable vocabularies designed to
encourage the reuse and extension of metadata semantics among
disparate information communities. the structural constraints rdf
imposes to support the consistent encoding and exchange of
standardized metadata provides for the interchangeability of separate
packages of metadata defined by different resource description
communities. </dc:Description>
<dc:Publisher>Corporation for National Research Initiatives</dc:Publisher>
<dc:Subject>
<rdf:Bag>
<rdf:li>machine-readable catalog record formats</rdf:li>
<rdf:li>applications of computer file organization and
access methods</rdf:li>
</rdf:Bag>
</dc:Subject>
<dc:Rights>Copyright @ 1998 Eric Miller</dc:Rights>
<dc:Type>Electronic Document</dc:Type>
<dc:Format>text/html</dc:Format>
<dc:Language>en</dc:Language>
<dc:Relation rdf:parseType="Resource">
<dcq:RelationType
rdf:resource="http://purl.org/metadata/dublin_core_qualifiers#IsPartOf"/>
<rdf:value resource="http://www.dlib.org/dlib/may98/05contents.html"/>
</dc:Relation>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,18 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating literal value -->
<rdf:RDF
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#">
<rdf:Description
xmlns:dc="http://purl.org/metadata/dublin_core#"
xmlns="http://www.w3.org/TR/REC-mathml"
rdf:about="http://mycorp.com/papers/NobelPaper1">
<dc:Title rdf:parseType="Literal">
Ramifications of <apply><power/><apply><plus/><ci>a</ci><ci>b</ci></apply>
<cn>2</cn></apply> to World Peace
</dc:Title>
<dc:Creator>David Hume</dc:Creator>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,15 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating literal value -->
<rdf:RDF
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:dc="http://purl.org/metadata/dublin_core#">
<rdf:Description about="http://www.foo.com/cool.html">
<dc:Creator>
<rdf:Seq ID="CreatorsAlphabeticalBySurname"
rdf:_1="Mary Andrew"
rdf:_2="Jacky Crystal"/>
</dc:Creator>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,15 @@
<?xml version='1.0'?>
<!-- Test inline description -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.swi.psy.uva.nl/projects/SWI-Prolog/">
<s:Creator rdf:ID="pl-creator">
<rdf:Description rdf:about="JW">
<s:name>Jan Wielemaker</s:name>
<s:works_at>SWI</s:works_at>
</rdf:Description>
</s:Creator>
</rdf:Description>
</rdf:RDF>

190
packages/RDF/suite/t38.rdf Normal file
View File

@ -0,0 +1,190 @@
<?xml version="1.0" encoding="iso-8859-1"?>
<!-- Definition of RDF-schema in itself -->
<!-- From http://www.w3.org/TR/rdf-schema/ -->
<rdf:RDF
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:rdfs="http://www.w3.org/2000/01/rdf-schema#">
<rdfs:Class rdf:ID="Resource">
<rdfs:label xml:lang="en">Resource</rdfs:label>
<rdfs:label xml:lang="fr">Ressource</rdfs:label>
<rdfs:comment>The most general class</rdfs:comment>
</rdfs:Class>
<rdf:Property about="http://www.w3.org/1999/02/22-rdf-syntax-ns#type">
<rdfs:label xml:lang="en">type</rdfs:label>
<rdfs:label xml:lang="fr">type</rdfs:label>
<rdfs:comment>Indicates membership of a class</rdfs:comment>
<rdfs:range rdf:resource="#Class"/>
</rdf:Property>
<rdf:Property ID="comment">
<rdfs:label xml:lang="en">comment</rdfs:label>
<rdfs:label xml:lang="fr">commentaire</rdfs:label>
<rdfs:domain rdf:resource="#Resource"/>
<rdfs:comment>Use this for descriptions</rdfs:comment>
<rdfs:range rdf:resource="#Literal"/>
</rdf:Property>
<rdf:Property ID="label">
<rdf:type resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
<rdfs:label xml:lang="en">label</rdfs:label>
<rdfs:label xml:lang="fr">label</rdfs:label>
<rdfs:domain rdf:resource="#Resource"/>
<rdfs:comment>Provides a human-readable version of a resource name.</rdfs:comment>
<rdfs:range rdf:resource="#Literal"/>
</rdf:Property>
<rdfs:Class rdf:ID="Class">
<rdfs:label xml:lang="en">Class</rdfs:label>
<rdfs:label xml:lang="fr">Classe</rdfs:label>
<rdfs:comment>The concept of Class</rdfs:comment>
<rdfs:subClassOf rdf:resource="#Resource"/>
</rdfs:Class>
<rdf:Property ID="subClassOf">
<rdfs:label xml:lang="en">subClassOf</rdfs:label>
<rdfs:label xml:lang="fr">sousClasseDe</rdfs:label>
<rdfs:comment>Indicates membership of a class</rdfs:comment>
<rdfs:range rdf:resource="#Class"/>
<rdfs:domain rdf:resource="#Class"/>
</rdf:Property>
<rdf:Property ID="subPropertyOf">
<rdfs:label xml:lang="en">subPropertyOf</rdfs:label>
<rdfs:label xml:lang="fr">sousPropriétéDe</rdfs:label>
<rdfs:comment>Indicates specialization of properties</rdfs:comment>
<rdfs:range rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
<rdfs:domain rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
</rdf:Property>
<rdf:Property ID="seeAlso">
<rdfs:label xml:lang="en">seeAlso</rdfs:label>
<rdfs:label xml:lang="fr">voirAussi</rdfs:label>
<rdfs:comment>Indicates a resource that provides information about the subject resource.</rdfs:comment>
<rdfs:range rdf:resource="http://www.w3.org/2000/01/rdf-schema#Resource"/>
<rdfs:domain rdf:resource="http://www.w3.org/2000/01/rdf-schema#Resource"/>
</rdf:Property>
<rdf:Property ID="isDefinedBy">
<rdf:type resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
<rdfs:subPropertyOf rdf:resource="#seeAlso"/>
<rdfs:label xml:lang="en">isDefinedBy</rdfs:label>
<rdfs:label xml:lang="fr">esDéfiniPar</rdfs:label>
<rdfs:comment>Indicates a resource containing and defining the subject resource.</rdfs:comment>
<rdfs:range rdf:resource="http://www.w3.org/2000/01/rdf-schema#Resource"/>
<rdfs:domain rdf:resource="http://www.w3.org/2000/01/rdf-schema#Resource"/>
</rdf:Property>
<rdfs:Class rdf:ID="ConstraintResource">
<rdfs:label xml:lang="en">ConstraintResource</rdfs:label>
<rdfs:label xml:lang="fr">RessourceContrainte</rdfs:label>
<rdf:type resource="#Class"/>
<rdfs:subClassOf rdf:resource="#Resource"/>
<rdfs:comment>Resources used to express RDF Schema constraints.</rdfs:comment>
</rdfs:Class>
<rdfs:Class rdf:ID="ConstraintProperty">
<rdfs:label xml:lang="en">ConstraintProperty</rdfs:label>
<rdfs:label xml:lang="fr">PropriétéContrainte</rdfs:label>
<rdfs:subClassOf rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
<rdfs:subClassOf rdf:resource="#ConstraintResource"/>
<rdfs:comment>Properties used to express RDF Schema constraints.</rdfs:comment>
</rdfs:Class>
<rdfs:ConstraintProperty rdf:ID="domain">
<rdfs:label xml:lang="en">domain</rdfs:label>
<rdfs:label xml:lang="fr">domaine</rdfs:label>
<rdfs:comment>This is how we associate a class with
properties that its instances can have</rdfs:comment>
</rdfs:ConstraintProperty>
<rdfs:ConstraintProperty rdf:ID="range">
<rdfs:label xml:lang="en">range</rdfs:label>
<rdfs:label xml:lang="fr">étendue</rdfs:label>
<rdfs:comment>Properties that can be used in a
schema to provide constraints</rdfs:comment>
<rdfs:range rdf:resource="#Class"/>
<rdfs:domain rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
</rdfs:ConstraintProperty>
<rdfs:Class rdf:about="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property">
<rdfs:label xml:lang="en">Property</rdfs:label>
<rdfs:label xml:lang="fr">Propriété</rdfs:label>
<rdfs:comment>The concept of a property.</rdfs:comment>
<rdfs:subClassOf rdf:resource="#Resource"/>
</rdfs:Class>
<rdfs:Class rdf:ID="Literal">
<rdfs:label xml:lang="en">Literal</rdfs:label>
<rdfs:label xml:lang="fr">Littéral</rdfs:label>
<rdf:type resource="#Class"/>
<rdfs:comment>This represents the set of atomic values, eg. textual strings.</rdfs:comment>
</rdfs:Class>
<rdfs:Class rdf:about="http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement">
<rdfs:label xml:lang="en">Statement</rdfs:label>
<rdfs:label xml:lang="fr">Déclaration</rdfs:label>
<rdfs:subClassOf rdf:resource="#Resource"/>
<rdfs:comment>This represents the set of reified statements.</rdfs:comment>
</rdfs:Class>
<rdf:Property about="http://www.w3.org/1999/02/22-rdf-syntax-ns#subject">
<rdfs:label xml:lang="en">subject</rdfs:label>
<rdfs:label xml:lang="fr">sujet</rdfs:label>
<rdfs:domain rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement"/>
<rdfs:range rdf:resource="#Resource"/>
</rdf:Property>
<rdf:Property about="http://www.w3.org/1999/02/22-rdf-syntax-ns#predicate">
<rdfs:label xml:lang="en">predicate</rdfs:label>
<rdfs:label xml:lang="fr">prédicat</rdfs:label>
<rdf:type resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
<rdfs:domain rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement"/>
<rdfs:range rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
</rdf:Property>
<rdf:Property about="http://www.w3.org/1999/02/22-rdf-syntax-ns#object">
<rdfs:label xml:lang="en">object</rdfs:label>
<rdfs:label xml:lang="fr">objet</rdfs:label>
<rdfs:domain rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Statement"/>
</rdf:Property>
<rdfs:Class rdf:ID="Container">
<rdfs:label xml:lang="en">Container</rdfs:label>
<rdfs:label xml:lang="fr">Enveloppe</rdfs:label>
<rdfs:subClassOf rdf:resource="#Resource"/>
<rdfs:comment>This represents the set Containers.</rdfs:comment>
</rdfs:Class>
<rdfs:Class rdf:about="http://www.w3.org/1999/02/22-rdf-syntax-ns#Bag">
<rdfs:label xml:lang="en">Bag</rdfs:label>
<rdfs:label xml:lang="fr">Ensemble</rdfs:label>
<rdfs:subClassOf rdf:resource="#Container"/>
</rdfs:Class>
<rdfs:Class rdf:about="http://www.w3.org/1999/02/22-rdf-syntax-ns#Seq">
<rdfs:label xml:lang="en">Sequence</rdfs:label>
<rdfs:label xml:lang="fr">Séquence</rdfs:label>
<rdfs:subClassOf rdf:resource="#Container"/>
</rdfs:Class>
<rdfs:Class rdf:about="http://www.w3.org/1999/02/22-rdf-syntax-ns#Alt">
<rdfs:label xml:lang="en">Alt</rdfs:label>
<rdfs:label xml:lang="fr">Choix</rdfs:label>
<rdfs:subClassOf rdf:resource="#Container"/>
</rdfs:Class>
<rdfs:Class rdf:ID="ContainerMembershipProperty">
<rdfs:label xml:lang="en">ContainerMembershipProperty</rdfs:label>
<rdfs:subClassOf rdf:resource="http://www.w3.org/1999/02/22-rdf-syntax-ns#Property"/>
</rdfs:Class>
<rdf:Property rdf:about="http://www.w3.org/1999/02/22-rdf-syntax-ns#value">
<rdfs:label xml:lang="en">object</rdfs:label>
<rdfs:label xml:lang="fr">value</rdfs:label>
</rdf:Property>
</rdf:RDF>

View File

@ -0,0 +1,25 @@
<?xml version='1.0' encoding='ISO-8859-1'?>
<!-- Version Wed Apr 12 12:09:19 CEST 2000 -->
<rdf:RDF
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:rdfs="http://www.w3.org/TR/1999/PR-rdf-schema-19990303#"
xmlns:rdfutil="http://www.w3.org/rdfutil#"
xmlns:protege="http://smi-web.stanford.edu/projects/protege/protege-rdf/protege-19992012#">
<rdf:Description rdf:ID="OntologyObjectMetaClass">
<rdf:type rdf:resource="http://www.w3.org/TR/1999/PR-rdf-schema-19990303#Class"/>
<rdfs:subClassOf rdf:resource="http://www.w3.org/TR/1999/PR-rdf-schema-19990303#Class"/>
<protege:abstractProperty>concrete</protege:abstractProperty>
</rdf:Description>
<rdf:Description rdf:ID="identifier">
<rdf:type rdf:resource="http://www.w3.org/TR/1999/PR-rdf-schema-19990303#Property"/>
<rdfutil:facets>
<rdfutil:facetResource>
<rdfutil:domain rdf:resource="#OntologyObjectMetaClass"/>
<rdfutil:range rdf:resource="http://www.w3.org/TR/xmlschema-2/#string"/>
<rdfutil:cardinality>1</rdfutil:cardinality>
</rdfutil:facetResource>
</rdfutil:facets>
</rdf:Description>
</rdf:RDF>

14
packages/RDF/suite/t4.rdf Normal file
View File

@ -0,0 +1,14 @@
<?xml version='1.0'?>
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.w3.org/Home/Lassila">
<s:Creator rdf:ID="statement1">Ora Lassila</s:Creator>
</rdf:Description>
<!-- The statement saying that i believe the above statement -->
<rdf:Description about="#statement1">
<s:believedBy>Stefan Decker</s:believedBy>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,11 @@
<?xml version='1.0'?>
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:my="http://www.mytypes.org/schema/">
<my:Bicycle wheels="2"/>
<rdf:Description type="http://www.mytypes.org/schema/Bicycle">
<my:wheels>2</my:wheels>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,15 @@
<?xml version="1.0"?>
<!-- Example from REC-rdf-syntax, demonstrating abbrevation -->
<RDF
xmlns="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:n="http://www.nist.gov/units/">
<Description about="John_Smith">
<n:weight rdf:ID="JohnWeight" rdf:parseType="Resource">
<rdf:value>200</rdf:value>
<n:units rdf:resource="http://www.nist.gov/units/Pounds"/>
</n:weight>
</Description>
</RDF>

View File

@ -0,0 +1,16 @@
<?xml version="1.0"?>
<!-- Test space handling for mixed literal/compound -->
<rdf:RDF
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#">
<rdf:Description about="John_Smith">
<a1>John</a1>
<a1>
<rdf:Description>
<v>200</v>
<t>pounds</t>
</rdf:Description>
</a1>
</rdf:Description>
</rdf:RDF>

15
packages/RDF/suite/t5.rdf Normal file
View File

@ -0,0 +1,15 @@
<?xml version='1.0'?>
<!-- Test inline description -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.swi.psy.uva.nl/projects/SWI-Prolog/">
<s:Creator rdf:ID="JW">
<rdf:Description>
<name>Jan Wielemaker</name>
<works_at>SWI</works_at>
</rdf:Description>
</s:Creator>
</rdf:Description>
</rdf:RDF>

15
packages/RDF/suite/t6.rdf Normal file
View File

@ -0,0 +1,15 @@
<?xml version='1.0'?>
<!-- Test attribute-bag -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.swi.psy.uva.nl/projects/xpce/">
<s:Creator>
<rdf:Bag>
<rdf:li>Jan Wielemaker</rdf:li>
<rdf:li>Anjo Anjewierden</rdf:li>
</rdf:Bag>
</s:Creator>
</rdf:Description>
</rdf:RDF>

17
packages/RDF/suite/t7.rdf Normal file
View File

@ -0,0 +1,17 @@
<?xml version='1.0'?>
<!-- Test attribute-bag -->
<rdf:RDF xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:s="http://description.org/schema/">
<rdf:Description about="http://www.swi.psy.uva.nl/projects/xpce/">
<s:Creator>
<rdf:Bag>
<rdf:li parseType="Resource">
<name>Jan Wielemaker</name>
<employed_at>SWI</employed_at>
</rdf:li>
</rdf:Bag>
</s:Creator>
</rdf:Description>
</rdf:RDF>

16
packages/RDF/suite/t8.rdf Normal file
View File

@ -0,0 +1,16 @@
<?xml version="1.0"?>
<!-- Copied from Pro Solutions RDF parser examples -->
<RDF xmlns="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:NIST="http://www.nist.gov/RDFschema/">
<Description about="John_Smith">
<NIST:Weight>
<Description ID="weight_001">
<NIST:Units rdf:resource="http://www.nist.gov/units/pounds"/>
<value xmlns="">200</value>
</Description>
</NIST:Weight>
</Description>
</RDF>

View File

@ -0,0 +1,22 @@
<rdf:RDF
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:rdfs="http://www.w3.org/2000/01/rdf-schema#"
xmlns:owl="http://www.w3.org/2002/07/owl#"
xmlns:first="http://www.w3.org/2002/03owlt/I5.8/inconsistent001#"
xml:base="http://www.w3.org/2002/03owlt/I5.8/inconsistent001" >
<rdf:Description rdf:ID="john">
<rdf:type>
<owl:Restriction>
<owl:onProperty>
<owl:DatatypeProperty rdf:ID="p">
<rdfs:range rdf:resource=
"http://www.w3.org/2001/XMLSchema#byte" />
</owl:DatatypeProperty>
</owl:onProperty>
<owl:cardinality
rdf:datatype="http://www.w3.org/2001/XMLSchema#nonNegativeInteger">257</owl:cardinality>
</owl:Restriction>
</rdf:type>
</rdf:Description>
</rdf:RDF>

View File

@ -0,0 +1,19 @@
<?xml version="1.0" encoding="iso-8859-1"?>
<!DOCTYPE rdf [
<!ENTITY rdf "http://www.w3.org/1999/02/22-rdf-syntax-ns#">
<!ENTITY xsd "http://www.w3.org/2000/10/XMLSchema#">
<!ENTITY t "http://www.swi.psy.uva.nl/test#">
]>
<rdf:RDF
xmlns:rdf ="&rdf;"
xmlns:xsd ="&xsd;"
xmlns:t="&t;"
>
<t:test rdf:ID="id1">
<t:a rdf:parseType="Literal"><b>strong</b></t:a>
</t:test>
</rdf:RDF>

View File

@ -0,0 +1,19 @@
<?xml version="1.0" encoding="iso-8859-1"?>
<!DOCTYPE rdf [
<!ENTITY rdf "http://www.w3.org/1999/02/22-rdf-syntax-ns#">
<!ENTITY xsd "http://www.w3.org/2000/10/XMLSchema#">
<!ENTITY t "http://www.swi.psy.uva.nl/test#">
]>
<rdf:RDF
xmlns:rdf ="&rdf;"
xmlns:xsd ="&xsd;"
xmlns:t="&t;"
>
<t:test rdf:ID="id1">
<t:int rdf:datatype="&xsd;int">42</t:int>
</t:test>
</rdf:RDF>

317
packages/RDF/test_rdf.pl Normal file
View File

@ -0,0 +1,317 @@
/* Part of SWI-Prolog
Author: Jan Wielemaker
E-mail: J.Wielemaker@uva.nl
WWW: http://www.swi-prolog.org
Copyright (C): 2010, University of Amsterdam
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
as published by the Free Software Foundation; either version 2
of the License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
As a special exception, if you link this library with other files,
compiled with a Free Software compiler, to produce an executable, this
library does not by itself cause the resulting executable to be covered
by the GNU General Public License. This exception does not however
invalidate any other reasons why the executable file might be covered by
the GNU General Public License.
*/
:- module(test_rdf,
[ suite/1, % +Test-number
test_dir/1, % +Directory
test_file/1, % +File
time_file/1, % +File
passed/1, % +Test-numberOrFile
test_rdf/0, % run whole suite
show_ok/1 % +Test
]).
:- multifile
user:file_search_path/2.
user:file_search_path(library, .).
user:file_search_path(library, '../sgml').
user:file_search_path(library, '../clib').
user:file_search_path(library, '..').
user:file_search_path(foreign, '../sgml').
user:file_search_path(foreign, '../clib').
user:file_search_path(foreign, '../semweb').
:- use_module(library(sgml)).
:- use_module(library(semweb/rdf_compare)).
:- use_module(library(rdf_parser)).
:- use_module(library(rdf_triple)).
:- use_module(library(rdf)).
:- use_module(pretty_print).
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
Test file for the SWI-Prolog RDF parser. Toplevel predicates:
# test/0
Run all tests from the `suite' directory and validate the
the result if the correct result is stored in a .ok file.
# suite(N)
Run test on suite/t<N>.rdf, showing RDF, intermediate
representation and triples on the console.
# passed(N)
Parse suite/t<N>.rdf and save the result in suite/t<N>.ok
The intention is to write tests, use suite/1 to make sure they are
parsed correctly and then run passed/1 to save the correct answer, so
running test/0 can validate all results.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
suite(N) :-
atomic_list_concat(['suite/t', N, '.rdf'], File),
test_file(File).
test_file(File) :-
rdf_reset_ids,
format('************* Test ~w ***~n', [File]),
cat(File),
load_structure(File,
[ RDFElement ],
[ dialect(xmlns),
space(sgml)
]),
rdf_start_file([], Cleanup),
make_rdf_state([base_uri('http://test.org/test/')], State, _),
xml_to_plrdf(RDFElement, RDF, State),
rdf_end_file(Cleanup),
format('============= Prolog term ==============~n', []),
pretty_print(RDF),
rdf_triples(RDF, Triples),
format('============= Triples ==================~n', []),
write_triples(Triples).
time_file(File) :-
time(load_rdf(File, Triples)),
length(Triples, Len),
format('Created ~w triples~n', [Len]).
passed(Id) :-
integer(Id), !,
atomic_list_concat(['suite/t', Id, '.rdf'], File),
passed(File).
passed(File) :-
rdf_reset_ids,
ok_file(File, OkFile),
load_rdf(File, Triples),
open(OkFile, write, Fd, [encoding(utf8)]),
save_triples(Triples, Fd),
close(Fd),
length(Triples, N),
format('Saved ~d triples to ~w~n', [N, OkFile]).
:- dynamic failed/1.
test_rdf :-
test(load_rdf),
test(process_rdf).
test(How) :-
retractall(failed(_)),
test_dir(suite, How),
findall(F, failed(F), Failed),
( Failed == []
-> true
; length(Failed, N),
format('ERROR: ~w tests failed~n', [N]),
fail
).
test_dir(Dir) :-
test_dir(Dir, load_rdf).
test_dir(Dir, How) :-
format('Tests from "~w" [~w]: ', [Dir, How]),
atom_concat(Dir, '/*.rdf', Pattern),
expand_file_name(Pattern, TestFiles),
maplist(test(How), TestFiles),
format(' done~n').
test(How, File) :-
format('.'), flush_output,
rdf_reset_ids,
ok_file(File, OkFile),
( call(How, File, Triples)
-> ( catch(open(OkFile, read, Fd, [encoding(utf8)]), _, fail)
-> ( read_triples(Fd, OkTriples),
close(Fd),
rdf_equal_graphs(Triples, OkTriples, _Subst)
-> true
; assert(failed(File)),
format('~N~w: WRONG ANSWER~n', [File])
)
; format('~N~w: (no .ok file)~n', [File])
)
; assert(failed(File)),
format('~N~w: PARSE FAILED~n', [File])
).
ok_file(File, OkFile) :-
file_base_name(File, BaseFile),
file_name_extension(Base, _, BaseFile),
file_directory_name(File, Dir),
atomic_list_concat([Dir, /, ok, /, Base, '.ok'], OkFile).
save_triples([], _).
save_triples([H|T], Fd) :-
format(Fd, '~q.~n', [H]),
save_triples(T, Fd).
read_triples(Fd, Terms) :-
read(Fd, T0),
read_triples(T0, Fd, Terms).
read_triples(end_of_file, _, []) :- !.
read_triples(rdf(S0,P0,O0), Fd, [rdf(S,P,O)|R]) :-
global_ref(S0, S),
global_ref(P0, P),
global_obj(O0, O),
read(Fd, T1),
read_triples(T1, Fd, R).
global_ref(rdf:Local, Global) :-
rdf_name_space(NS), !,
atom_concat(NS, Local, Global).
global_ref(NS:Local, Global) :- !,
atom_concat(NS, Local, Global).
global_ref(URI, URI).
global_obj(literal(X), literal(X)) :- !.
global_obj(Local, Global) :-
global_ref(Local, Global).
write_triples([]) :- !.
write_triples([H|T]) :- !,
write_triple(H),
write_triples(T).
write_triple(Triple) :-
is_rdf_triple(Triple), !,
Triple = rdf(S,P,O),
format('{~q, ~q, ~q}~n', [S,P,O]).
write_triple(Triple) :-
format('@@@@@ Bad Triple: ~p~n', [Triple]),
fail.
cat(File) :-
open(File, read, Fd),
copy_stream_data(Fd, user_output),
close(Fd).
:- dynamic triple/1.
process_rdf(File, Triples) :-
retractall(triple(_)),
process_rdf(File, assert_triples, []),
findall(T, retract(triple(T)), Triples).
assert_triples([], _).
assert_triples([H|T], Loc) :-
assert(triple(H)),
assert_triples(T, Loc).
/*******************************
* VALIDATE *
*******************************/
is_rdf_triple(rdf(Subject, Predicate, Object)) :-
is_subject(Subject),
is_predicate(Predicate),
is_object(Object).
is_subject(0) :- !, fail. % Variables
is_subject(URI) :- is_uri(URI), !.
is_subject(each(URI)) :- is_uri(URI), !.
is_subject(prefix(Pattern)) :-
atom(Pattern), !.
is_predicate(0) :- !, fail.
is_predicate(rdf:RdfPred) :- !,
is_rdf_predicate(RdfPred).
is_predicate(NS:Pred) :- !,
atom(NS),
atom(Pred).
is_predicate(Pred) :-
atom(Pred).
is_object(0) :- !,
fail.
is_object(literal(XML)) :- !,
is_xml(XML).
is_object(rdf:RdfType) :- !,
is_rdf_type(RdfType).
is_object(URI) :-
is_uri(URI).
is_object(Subject) :-
is_subject(Subject), !.
is_object(Pred) :-
is_predicate(Pred), !.
is_uri(URI) :- atom(URI).
is_xml(_XML). % for now
is_rdf_predicate(RdfPred) :- atom(RdfPred).
is_rdf_type(RdfType) :- atom(RdfType).
/*******************************
* UTIL *
*******************************/
% find_rdf(+XMLTerm, -RDFTerm)
%
% If the document contains an embedded RDF term, return it, else
% return the whole document. The latter is a bit dubious, but good
% for the purpose of this test-file
find_rdf(Term, RDFTerm) :-
RDFTerm = element(NS:'RDF', _, _),
term_member(RDFTerm, Term), !,
( rdf_name_space(NS)
-> true
; assert(rdf_parser:rdf_name_space(NS)),
assert(new_rdf_namespace(NS))
).
find_rdf(Term, Term).
term_member(X, X).
term_member(X, Compound) :-
compound(Compound),
arg(_, Compound, Arg),
term_member(X, Arg).
/*******************************
* SHOW DIAGRAM *
*******************************/
show_ok(Test) :-
ok_file(Test, File),
open(File, read, Fd, [encoding(utf8)]),
read_triples(Fd, OkTriples),
close(Fd),
new(D, rdf_diagram(string('Ok for %s', File))),
send(D, triples, OkTriples),
send(D, open).

162
packages/RDF/test_write.pl Normal file
View File

@ -0,0 +1,162 @@
/* $Id$
Part of SWI-Prolog
Author: Jan Wielemaker
E-mail: wielemak@science.uva.nl
WWW: http://www.swi-prolog.org
Copyright (C): 1985-2007, University of Amsterdam
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
as published by the Free Software Foundation; either version 2
of the License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
As a special exception, if you link this library with other files,
compiled with a Free Software compiler, to produce an executable, this
library does not by itself cause the resulting executable to be covered
by the GNU General Public License. This exception does not however
invalidate any other reasons why the executable file might be covered by
the GNU General Public License.
*/
:- module(test_rdf_write,
[ test_write/0,
run_tests/0,
run_tests/1
]).
:- asserta(user:file_search_path(foreign, '../sgml')).
:- asserta(user:file_search_path(foreign, '../semweb')).
:- asserta(user:file_search_path(foreign, '../clib')).
:- asserta(user:file_search_path(library, '..')).
:- asserta(user:file_search_path(library, '../sgml')).
:- asserta(user:file_search_path(library, '.')).
:- asserta(user:file_search_path(library, '../plunit')).
:- asserta(user:file_search_path(library, '../clib')).
:- use_module(library(plunit)).
:- use_module(library(rdf_write)).
:- use_module(library(sgml)).
:- use_module(library(lists)).
:- use_module(library(debug)).
:- use_module(library(semweb/rdf_db)).
:- use_module(rdf).
test_write :-
run_tests([ rdf_write
]).
/*******************************
* ROUND TRIP *
*******************************/
test_graph(Triples) :-
tmp_file(rdf, Tmp),
open(Tmp, write, Out, [encoding(utf8)]),
rdf_write_xml(Out, Triples),
close(Out),
load_rdf(Tmp, ReadTriples),
delete_file(Tmp),
compare_triples(Triples, ReadTriples, _).
/*******************************
* COMPARING *
*******************************/
% compare_triples(+PlRDF, +NTRDF, -Substitions)
%
% Compare two models and if they are equal, return a list of
% PlID = NTID, mapping NodeID elements.
compare_triples(A, B, Substitutions) :-
compare_list(A, B, [], Substitutions), !.
compare_list([], [], S, S).
compare_list([H1|T1], In2, S0, S) :-
select(H2, In2, T2),
compare_triple(H1, H2, S0, S1),
compare_list(T1, T2, S1, S).
compare_triple(rdf(Subj1,P1,O1), rdf(Subj2, P2, O2), S0, S) :-
compare_field(Subj1, Subj2, S0, S1),
compare_field(P1, P2, S1, S2),
compare_field(O1, O2, S2, S).
compare_field(X, X, S, S) :- !.
compare_field(literal(X), xml(X), S, S) :- !. % TBD
compare_field(rdf:Name, Atom, S, S) :-
atom(Atom),
rdf_parser:rdf_name_space(NS),
atom_concat(NS, Name, Atom), !.
compare_field(NS:Name, Atom, S, S) :-
atom(Atom),
atom_concat(NS, Name, Atom), !.
compare_field(X, Id, S, S) :-
memberchk(X=Id, S), !.
compare_field(X, Y, S, [X=Y|S]) :-
\+ memberchk(X=_, S),
rdf_is_bnode(X),
rdf_is_bnode(Y),
debug(bnode, 'Assume ~w = ~w~n', [X, Y]).
/*******************************
* TESTS *
*******************************/
:- begin_tests(rdf_write).
test(1, true) :-
test_graph([ rdf(s, p, o)
]).
test(anon_s, true) :-
test_graph([ rdf('__s', p, o)
]).
test(anon_o, true) :-
test_graph([ rdf(s, p, '__o')
]).
test(anon_loop, blocked('NodeID map must check for cycles')) :-
test_graph([ rdf('__r1', p1, '__r2'),
rdf('__r2', p1, '__r1')
]).
test(anon_loop, true) :-
test_graph([ rdf('__r1', p1, '__r2'),
rdf('__r1', p2, '__r2'),
rdf('__r2', p1, '__r1'),
rdf('__r2', p2, '__r1')
]).
test(anon_reuse, true) :-
test_graph([ rdf('__s1', p1, '__o1'),
rdf('__s2', p1, '__o1')
]).
test(anon_reuse, true) :-
test_graph([ rdf('__s1', p1, '__o1'),
rdf('__s2', p1, '__o1'),
rdf('__o1', name, literal(foo))
]).
test(literal, true) :-
test_graph([ rdf(s, p, literal(hello))
]).
test(lang, true) :-
test_graph([ rdf(s, p, literal(lang(en, hello)))
]).
test(type, true) :-
test_graph([ rdf(s, p, literal(type(t, hello)))
]).
:- end_tests(rdf_write).

467
packages/RDF/w3c_test.pl Normal file
View File

@ -0,0 +1,467 @@
/* $Id$
Part of SWI-Prolog SGML/XML parser
Author: Jan Wielemaker
E-mail: jan@swi.psy.uva.nl
WWW: http://www.swi.psy.uva.nl/projects/SWI-Prolog/
Copying: LGPL-2. See the file COPYING or http://www.gnu.org
Copyright (C) 1990-2002 SWI, University of Amsterdam. All rights reserved.
*/
:- module(rdf_w3c_test,
[ process_manifest/0,
process_manifest/1,
run_tests/0, % run all tests
run/0, % run selected test
show/1, % RDF diagram for File
run_test/1 % run a single test
]).
% get libraries locally
:- asserta(user:file_search_path(library, '.')).
:- use_module(rdf). % our RDF parser
:- use_module(rdf_ntriples). % read .nt files
:- load_files([ library(pce),
library(toolbar),
library(pce_report),
rdf_diagram,
library('emacs/emacs')
],
[ silent(true)
]).
:- dynamic
verbose/0.
%verbose.
set_verbose :-
verbose, !.
set_verbose :-
assert(verbose).
:- dynamic
rdf/3.
ns(test,
'http://www.w3.org/2000/10/rdf-tests/rdfcore/testSchema#').
local('http://www.w3.org/2000/10/rdf-tests/rdfcore/',
'W3Ctests/').
process_manifest :-
process_manifest('W3Ctests/Manifest.rdf').
process_manifest(Manifest) :-
retractall(rdf(_,_,_)),
load_rdf(Manifest, Triples),
assert_triples(Triples).
assert_triples([]).
assert_triples([rdf(S, P, O)|T]) :-
canonise(S, Subject),
canonise(P, Predicate),
canonise(O, Object),
assert(rdf(Subject, Predicate, Object)),
assert_triples(T).
canonise(NS:Name, N:Name) :-
ns(N, NS), !.
canonise(Absolute, N:Name) :-
atom(Absolute),
ns(N, NS),
atom_concat(NS, Name, Absolute), !.
canonise(X, X).
run_tests :-
process_manifest,
start_tests,
( rdf(About, rdf:type, test:Type),
\+ rdf(About, test:status, literal('OBSOLETE')),
test_type(Type),
% once(run_test(About)), % Should not be needed
run_test(About),
fail
; true
), !,
report_results.
test_type('PositiveParserTest').
%test_type('NegativeParserTest').
run_test(Test) :-
rdf(Test, test:inputDocument, In),
local_file(In, InFile),
exists_file(InFile),
( load_rdf(InFile, RDF,
[ base_uri(In),
expand_foreach(true)
])
-> true
; RDF = []
),
Data = [ source(InFile),
result(RDF),
norm(NT),
substitutions(Substitions)
],
% there may be alternative output
% documents
( rdf(Test, test:outputDocument, Out),
local_file(Out, NTFile),
load_rdf_ntriples(NTFile, NT),
feedback('Comparing to ~w~n', [NTFile]),
compare_triples(RDF, NT, Substitions)
-> test_result(pass, Test, Data)
% if all fails, display the first
; rdf(Test, test:outputDocument, Out),
local_file(Out, NTFile),
load_rdf_ntriples(NTFile, NT),
Substitions = [],
test_result(fail, Test, Data)
).
local_file(URL, File) :-
local(URLPrefix, FilePrefix),
atom_concat(URLPrefix, Base, URL), !,
atom_concat(FilePrefix, Base, File).
/*******************************
* GUI *
*******************************/
:- pce_begin_class(w3c_rdf_test_gui, frame).
initialise(F, Show:chain) :->
send_super(F, initialise, 'W3C RDF test suite results'),
send(F, append, new(B, browser)),
send(B, hor_stretch, 100),
send(B, hor_shrink, 100),
( send(Show, member, source)
-> new(V, emacs_view(height := 3)),
send(V, name, text)
; true
),
( send(Show, member, result)
-> new(R, rdf_diagram),
send(R, name, result),
send(R, label, 'Result')
; true
),
( send(Show, member, norm)
-> new(N, rdf_diagram),
send(N, name, norm),
send(N, label, 'Norm')
; true
),
stack_windows([V,R,N], _, W),
( nonvar(W)
-> send(W, right, B)
; true
),
send(new(D, tool_dialog(F)), above, B),
send(new(report_dialog), below, B),
send(F, fill_menu, D),
send(F, fill_browser, B).
stack_windows([], L, L).
stack_windows([H|T], W0, W) :-
var(H), !,
stack_windows(T, W0, W).
stack_windows([H|T], W0, W) :-
var(W0), !,
stack_windows(T, H, W).
stack_windows([H|T], WL, W) :-
send(H, below, WL),
stack_windows(T, H, W).
fill_menu(F, D:tool_dialog) :->
send_list(D,
[ append(menu_item(exit, message(F, destroy)),
file)
]).
fill_browser(_F, B:browser) :->
send(B, style, pass, style(colour := dark_green)),
send(B, style, fail, style(colour := red)),
send(B?image, recogniser,
handler(ms_right_down,
and(message(B, selection,
?(B, dict_item, @event)),
new(or)))),
send(B, popup, new(P, popup)),
send(B, select_message, message(@arg1, run)),
send_list(P, append,
[ menu_item(run,
message(@arg1, run)),
menu_item(edit,
message(@arg1, edit_test)),
gap,
menu_item(show_result,
message(@arg1, show_triples, result)),
menu_item(show_norm,
message(@arg1, show_triples, norm)),
gap,
menu_item(discussion,
message(@arg1, open_url, discussion),
condition :=
message(@arg1, has_url, discussion)),
menu_item(approval,
message(@arg1, open_url, approval),
condition :=
message(@arg1, has_url, approval)),
gap,
menu_item(copy_test_uri,
message(@arg1, copy_test_uri))
]).
test_result(F, Result:{pass,fail}, Test:name, Data:prolog) :->
"Test failed"::
get(F, member, browser, B),
( get(B, member, Test, Item)
-> send(Item, object, prolog(Data)),
send(Item, style, Result)
; send(B, append,
rdf_test_item(Test, @default, prolog(Data), Result))
).
clear(F) :->
get(F, member, browser, B),
send(B, clear).
summarise(F) :->
get(F, member, browser, Browser),
new(Pass, number(0)),
new(Fail, number(0)),
send(Browser?members, for_all,
if(@arg1?style == pass,
message(Pass, plus, 1),
message(Fail, plus, 1))),
send(F, report, status, '%d tests succeeded; %d failed',
Pass, Fail).
:- pce_end_class(w3c_rdf_test_gui).
:- pce_begin_class(rdf_test_item, dict_item).
edit_test(Item) :->
"Edit input document of test"::
get(Item, object, List),
member(source(InFile), List),
edit(file(InFile)).
show_triples(Item, Set:{result,norm}) :->
"Show result of our parser"::
get(Item, key, Test),
get(Item, object, List),
Term =.. [Set,Triples],
member(Term, List),
send(Item, show_diagram(Triples,
string('%s for %s', Set?label_name, Test))).
show_diagram(_Item, Triples:prolog, Label:name) :->
"Show diagram for triples"::
new(D, rdf_diagram(Label)),
send(new(report_dialog), below, D),
send(D, triples, Triples),
send(D, open).
open_url(Item, Which:name) :->
"Open associated URL in browser"::
get(Item, key, Test),
rdf(Test, test:Which, URL),
www_open_url(URL).
has_url(Item, Which:name) :->
"Test if item has URL"::
get(Item, key, Test),
rdf(Test, test:Which, _URL).
run(Item) :->
"Re-run the test"::
get(Item, key, Test),
run_test(Test),
send(Item, show).
copy_test_uri(Item) :->
"Copy URI of test to clipboard"::
get(Item, key, Test),
send(@display, copy, Test).
show(Item) :->
"Show source, result and norm diagrams"::
get(Item?image, frame, Frame),
get(Item, object, List),
( get(Frame, member, result, Result)
-> member(result(RTriples), List),
send(Result, triples, RTriples)
; true
),
( get(Frame, member, norm, Norm)
-> member(norm(NTriples), List),
send(Norm, triples, NTriples)
; true
),
( get(Frame, member, text, View)
-> member(source(File), List),
send(View, text_buffer, new(TB, emacs_buffer(File))),
% scroll to RDF text
( member(Pattern, [':RDF', 'RDF']),
get(TB, find, 0, Pattern, Start),
get(TB, scan, Start, line, 0, start, BOL)
-> send(View, scroll_to, BOL, 1)
; true
)
; true
).
% member(substitutions(Substitutions), List),
% send(Result, copy_layout, Norm, Substitutions),
:- pce_end_class(rdf_test_item).
:- pce_global(@rdf_test_gui, make_rdf_test_gui).
make_rdf_test_gui(Ref) :-
send(new(Ref, w3c_rdf_test_gui(chain(source,result))), open).
test_result(Result, Test, Data) :-
send(@rdf_test_gui, test_result, Result, Test, Data),
( Result == fail, verbose
-> member(result(Our), Data),
length(Our, OurLength),
format('~N** Our Triples (~w)~n', OurLength),
pp(Our),
member(norm(Norm), Data),
length(Norm, NormLength),
format('~N** Normative Triples (~w)~n', NormLength),
pp(Norm)
; true
).
start_tests :-
send(@rdf_test_gui, clear).
report_results :-
send(@rdf_test_gui, summarise).
run :-
set_verbose,
get(@rdf_test_gui, member, browser, B),
get(B, selection, DI),
get(DI, key, Test),
run_test(Test).
/*******************************
* SHOW A FILE *
*******************************/
show(File) :-
rdf_diagram_from_file(File).
/*******************************
* COMPARING *
*******************************/
% compare_triples(+PlRDF, +NTRDF, -Substitions)
%
% Compare two models and if they are equal, return a list of
% PlID = NTID, mapping NodeID elements.
compare_triples(A, B, Substitutions) :-
compare_list(A, B, [], Substitutions).
compare_list([], [], S, S).
compare_list(L1, L2, S0, S) :-
take_bag(L1, B1, E1, R1), !,
take_bag(L2, B2, E2, R2),
compare_field(B1, B2, S0, S1),
compare_bags(E1, E2, S1, S2),
compare_list(R1, R2, S2, S).
compare_list([H1|T1], In2, S0, S) :-
select(H2, In2, T2),
compare_triple(H1, H2, S0, S1), % put(.), flush_output,
compare_list(T1, T2, S1, S).
compare_triple(rdf(Subj1,P1,O1), rdf(Subj2, P2, O2), S0, S) :-
compare_field(Subj1, Subj2, S0, S1),
compare_field(P1, P2, S1, S2),
compare_field(O1, O2, S2, S).
compare_field(X, X, S, S) :- !.
compare_field(literal(X), xml(X), S, S) :- !. % TBD
compare_field(rdf:Name, Atom, S, S) :-
atom(Atom),
rdf_parser:rdf_name_space(NS),
atom_concat(NS, Name, Atom), !.
compare_field(NS:Name, Atom, S, S) :-
atom(Atom),
atom_concat(NS, Name, Atom), !.
compare_field(X, node(Id), S, S) :-
memberchk(X=Id, S), !.
compare_field(X, node(Id), S, [X=Id|S]) :-
\+ memberchk(X=_, S),
atom(X),
generated_prefix(Prefix),
sub_atom(X, 0, _, _, Prefix), !,
feedback('Assume ~w = ~w~n', [X, node(Id)]).
generated_prefix(Prefix) :-
rdf_truple:anon_base(Prefix).
% compare_bags(+Members1, +Members2, +S0, -S)
%
% Order of _1, _2, etc. are not relevant in BadID reification. Are
% they in general? Anyway, we'll normalise the order of the bags
compare_bags([], [], S, S).
compare_bags([E1|T1], M, S0, S) :-
select(E2, M, T2),
compare_field(E1, E2, S0, S1),
compare_bags(T1, T2, S1, S).
take_bag(Triples, Bag, Elems, RestTriples) :-
select(rdf(Bag, Type, BagClass), Triples, T1),
compare_field(rdf:type, Type, [], []),
compare_field(rdf:'Bag', BagClass, [], []),
bag_members(T1, Bag, Elems, RestTriples).
bag_members([], _, [], []).
bag_members([rdf(Bag, IsElm, E)|T], Bag, [E|ET], Rest) :-
member_prop(IsElm), !,
bag_members(T, Bag, ET, Rest).
bag_members([T0|T], Bag, Elems, [T0|R]) :-
bag_members(T, Bag, Elems, R).
member_prop(rdf:Name) :-
atom_codes(Name, [0'_|Codes]),
number_codes(_N, Codes), !.
member_prop(Prop) :-
atom(Prop),
rdf_parser:rdf_name_space(NS),
atom_concat(NS, Name, Prop),
atom_codes(Name, [0'_|Codes]),
number_codes(_N, Codes), !.
% feedback(+Format, +Args)
%
% Print if verbose
feedback(Fmt, Args) :-
verbose, !,
format(user_error, Fmt, Args).
feedback(_, _).

Some files were not shown because too many files have changed in this diff Show More