The file library(semweb/rdf_db) provides the core of the SWI-Prolog RDF store.
literal(Value)
if the
object is a literal value. If a value of the form
NameSpaceID:LocalName is provided it is expanded to a ground
atom using expand_goal/2. This implies you can use this
construct in compiled code without paying a performance penalty.
Literal values take one of the following forms:
rdf:datatype
TypeID. The Value is either the textual representation or a
natural Prolog representation. See the option
convert_typed_literal(:Convertor) of the parser. The storage
layer provides efficient handling of atoms, integers (64-bit)
and floats (native C-doubles). All other data is represented
as a Prolog record.
For literal querying purposes, Object can be of the form
literal(+Query, -Value)
, where Query is one of the terms below.
If the Query takes a literal argument and the value has a
numeric type numerical comparison is performed.
icase(Text)
. Backward compatibility.
Backtracking never returns duplicate triples. Duplicates can be
retrieved using rdf/4. The predicate rdf/3 raises a type-error
if called with improper arguments. If rdf/3 is called with a
term literal(_)
as Subject or Predicate object it fails
silently. This allows for graph matching goals like
rdf(S,P,O)
,rdf(O,P2,O2)
to proceed without errors.
rdf(Subject, Predicate, Object)
is true
exploiting the rdfs:subPropertyOf predicate as well as inverse
predicates declared using rdf_set_predicate/2 with the
inverse_of
property.inverse_of(Pred)
.symetric(true)
or inverse_of(P2)
properties.
If used with either Subject or Object unbound, it first returns the origin, followed by the reachable nodes in breadth-first search-order. The implementation internally looks one solution ahead and succeeds deterministically on the last solution. This predicate never generates the same node twice and is robust against cycles in the transitive relation.
With all arguments instantiated, it succeeds deterministically if a path can be found from Subject to Object. Searching starts at Subject, assuming the branching factor is normally lower. A call with both Subject and Object unbound raises an instantiation error. The following example generates all subclasses of rdfs:Resource:
?- rdf_reachable(X, rdfs:subClassOf, rdfs:'Resource'). X = 'http://www.w3.org/2000/01/rdf-schema#Resource' ; X = 'http://www.w3.org/2000/01/rdf-schema#Class' ; X = 'http://www.w3.org/1999/02/22-rdf-syntax-ns#Property' ; ...
infinite
to impose no
distance-limit.This predicate is primarily intended as a way to process all resources without processing resources twice. The user must be aware that some of the returned resources may not appear in any visible triple.
user
. Subject and Predicate are
resources. Object is either a resource or a term literal(Value)
.
See rdf/3 for an explanation of Value for typed and language
qualified literals. All arguments are subject to name-space
expansion. Complete duplicates (including the same graph and
`line' and with a compatible `lifespan') are not added to the
database.literal(Value)
._:
. For backward compatibility reason, __
is also
considered to be a blank node.
Plain literals | Atom |
Language tagged literal | Atom holding plain text |
xsd:string | Atom |
rdf:XMLLiteral | XML DOM Tree |
Numeric XSD type | Number |
__rdf_GC
performs garbage collection as long as
it is considered `useful'.
Using rdf_gc/0 should only be needed to ensure a fully clean database for analysis purposes such as leak detection.
triples
for the interpretation of this value.
Note that resources that have rdf:type
rdf:Property
are
not automatically included in the result-set of this predicate,
while all resources that appear as the second argument of a
triple are included.
inverse_of(Self)
.rdf_subject_branch_factor
property, uniqueness of the object value is computed from the
hash key rather than the actual values.rdf_subject_branch_factor
, but also considering
triples of `subPropertyOf' this relation. See also rdf_has/3.rdf_object_branch_factor
, but also considering
triples of `subPropertyOf' this relation. See also rdf_has/3.symmetric(true)
is the same as inverse_of(Predicate)
,
i.e., creating a predicate that is the inverse of
itself.inverse_of([])
.
The transitive
property is currently not used. The symmetric
and inverse_of
properties are considered by rdf_has/3,4 and
rdf_reachable/3.
snapshot
option. A
snapshot created outside a transaction exists until it is
deleted. Snapshots taken inside a transaction can only be used
inside this transaction.rdf_transaction(Goal, user, [])
. See rdf_transaction/3.rdf_transaction(Goal, Id, [])
. See rdf_transaction/3.Processed options are:
true
, which implies that an anonymous snapshot is
created at the current state of the store. Modifications
due to executing Goal are only visible to Goal.The duplicates marks are used to reduce the administrative load of avoiding duplicate answers. Normally, the duplicates are marked using a background thread that is started on the first query that produces a substantial amount of duplicates.
This predicate is normally executed from a background thread named =__rdf_duplicate_detecter= which is created when a query discovers that checking for duplicates becomes too expensive.
rdf_load(FileOrList, [])
. See rdf_load/2.share
(default),
equivalent blank nodes are shared in the same resource.file://
URL when loading
a file or, if the specification is a URL, its normalized
version without the optional #fragment.true
, changed
(default) or
not_loaded
.not_modified
, cached(File)
,
last_modified(Stamp)
or unknown
.false
, do not use or create a cache file.true
(default false
), register xmlns
namespace
declarations or Turtle @prefix
prefixes using
rdf_register_prefix/3 if there is no conflict.true
, the message reporting completion is printed using
level silent
. Otherwise the level is informational
. See
also print_message/2.Other options are forwarded to process_rdf/3. By default, rdf_load/2 only loads RDF/XML from files. It can be extended to load data from other formats and locations using plugins. The full set of plugins relevant to support different formats and locations is below:
:- use_module(library(semweb/turtle)). % Turtle and TriG :- use_module(library(semweb/rdf_ntriples)). :- use_module(library(semweb/rdf_zlib_plugin)). :- use_module(library(semweb/rdf_http_plugin)). :- use_module(library(http/http_ssl_plugin)).
modified(false)
.Additional graph properties can be added by defining rules for the multifile predicate property_of_graph/2. Currently, the following extensions are defined:
true
if the graph is persistent.rdf_save(Out, [])
. See rdf_save/2 for details.false
(default true
) do not save blank nodes that do
not appear (indirectly) as object of a named resource.write_xml_base
option.xml:lang
saved with rdf:RDF element.true
(default false
), inline resources when
encountered for the first time. Normally, only bnodes
are handled this way.true
(default false
), emit subjects sorted on
the full URI. Useful to make file comparison easier.false
, do not include the xml:base
declaration that is written normally when using the
base_uri
option.false
(default true
), never use xml attributes to
save plain literal attributes, i.e., always used an XML
element as in <name>Joe</name>
.Save an RDF header, with the XML header, DOCTYPE, ENTITY and opening the rdf:RDF element with appropriate namespace declarations. It uses the primitives from section 3.5 to generate the required namespaces and desired short-name. Options is one of:
rdf
and rdfs
are added to the provided List. If a namespace is not
declared, the resource is emitted in non-abreviated form.call(Filter, Where, Prefix, URI)
The Where argument gives the location of the prefix ans is
one of subject
, predicate
, object
or type
. The
Prefix argument is the potentionally new prefix and URI is
the full URI that is being processed.
call(Goal,S,P,O,Graph)
icase
, substring
, word
, prefix
or like
. For backward
compatibility, exact
is a synonym for icase
.not(Key)
. If not-terms are provided, there
must be at least one positive keywords. The negations are tested
after establishing the positive matches.key(+Key)
Succeeds if Key is a key in the map and unify Answer with the
number of values associated with the key. This provides a fast
test of existence without fetching the possibly large
associated value set as with rdf_find_literal_map/3.prefix(+Prefix)
Unify Answer with an ordered set of all keys that have the
given prefix. See section 3.1 for details on prefix matching.
Prefix must be an atom. This call is intended for
auto-completion in user interfaces.ge(+Min)
Unify Answer with all keys that are larger or equal to the
integer Min.le(+Max)
Unify Answer with all keys that are smaller or equal to the integer
Max.between(+Min, +Max)
Unify
Answer with all keys between Min and Max (including).Major*10000 + Minor*100 + Patch.
s
,
p
, sp
, o
, po
, spo
, g
, sg
or pg
. Parameter
is one of:
permission_error
exception.When inside a transaction, Generation is unified to a term TransactionStartGen + InsideTransactionGen. E.g., 4+3 means that the transaction was started at generation 4 of the global database and we have created 3 new generations inside the transaction. Note that this choice of representation allows for comparing generations using Prolog arithmetic. Comparing a generation in one transaction with a generation in another transaction is meaningless.
The following predicates are re-exported from other modules
Note that this predicate is a meta-predicate on its output argument. This is necessary to get the module context while the first argument may be of the form (:)/2. The above mode description is correct, but should be interpreted as (?,?).
rdf_current_prefix(Prefix, Expansion), atom_concat(Expansion, Local, URI),
true
, replace existing namespace alias. Please note
that replacing a namespace is dangerous as namespaces
affect preprocessing. Make sure all code that depends on
a namespace is compiled after changing the registration.true
and Alias is already defined, keep the
original binding for Prefix and succeed silently.Without options, an attempt to redefine an alias raises a permission error.
Predefined prefixes are:
Terms of the form Prefix:Local
that appear in TermIn for which
Prefix is not defined are not replaced. Unlike rdf_global_id/2 and
rdf_global_object/2, no error is raised.
true
, replace existing namespace alias. Please note
that replacing a namespace is dangerous as namespaces
affect preprocessing. Make sure all code that depends on
a namespace is compiled after changing the registration.true
and Alias is already defined, keep the
original binding for Prefix and succeed silently.Without options, an attempt to redefine an alias raises a permission error.
Predefined prefixes are:
As it is subject to term_expansion/2, the rdf_meta/1 declaration
can only be used as a directive. The directive must be processed
before the definition of the predicates as well as before
compiling code that uses the rdf meta-predicates. The atom
rdf_meta
is declared as an operator exported from
library(semweb/rdf_db). Files using rdf_meta/1 must explicitely
load this library.
Beginning with SWI-Prolog 7.3.17, the low-level RDF interface
(rdf/3, rdf_assert/3, etc.) perform runtime expansion of
Prefix:Local
terms. This eliminates the need for rdf_meta/1
for simple cases. However, runtime expansion comes at a
significant overhead and having two representations for IRIs (a
plain atom and a term Prefix:Local
) implies that simple
operations such as comparison of IRIs no longer map to native
Prolog operations such as IRI1 == IRI2
.
The following predicates are exported, but not or incorrectly documented.