This module extends module `rdf_prefixes' that is part of the
standards SWI-Prolog distribution.
- To be done
- - There is currently no way to retract prefix declarations.
- assert_prefixes(+File:atom) is det
- Asserts prefixes that appear at the top of the given N-Quads,
N-Triples, TriG, or Turtle file.
- rdf_prefix(+Alias:atom) is semidet
- rdf_prefix(-Alias:atom) is nondet
- rdf_prefix_append(+Lists:list(list), +List:list) is semidet
- rdf_prefix_append(+Lists:list(list), -List:list) is det
- rdf_prefix_iri(-Alias:atom, -Local:atom, +Iri:atom) is det
- rdf_prefix_iri(+Alias:atom, +Local:atom, -Iri:atom) is det
- rdf_prefix_iri(+Alias:atom, +Local:list(atom), -Iri:atom) is det
-
- See also
- - Like rdf_prefix_iri/2, but works with maplist/3.
- rdf_prefix_map(-Alias2Prefix:assoc(atom,iri)) is det
- rdf_prefix_maplist(:Goal_1, +Args1:list) is det
- rdf_prefix_maplist(:Goal_2, +Args1:list, +Args2:list) is det
- rdf_prefix_maplist(:Goal_3, +Args1:list, +Args2:list, +Args3:list) is det
- rdf_prefix_member(?Elem, +L:list) is nondet
- Calls member/2 under RDF prefix expansion.
- rdf_prefix_memberchk(?Elem, +L:list) is nondet
- Calls memberchk/2 under RDF prefix expansion.
- rdf_prefix_selectchk(+Elem, +L:list, -Rest:list) is det
- Calls selectchk/3 under RDF prefix expansion.
- rdf_register_prefix(+PairOrAlias:or([atom,pair(atom)])) is det
- Syntactic variant of rdf_register_prefix/2 that allows for pair
notation (i.e., pairs of the form `Alias-Prefix'), which in
convenient in combination with maplist/2.
- rdf_register_prefixes is det
- Registers RDF prefixes that are standardized and/or commonly used
in the LOD Cloud.
Re-exported predicates
The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.
- rdf_prefix(:Alias, +URI) is det
- Register a local prefix. This declaration takes precedence
over globally defined prefixes using rdf_register_prefix/2,3.
Module local prefixes are notably required to deal with SWISH,
where users need to be able to have independent namespace
declarations.
- rdf_register_prefix(+Prefix, +URI) is det
- rdf_register_prefix(+Prefix, +URI, +Options) is det
- Register Prefix as an abbreviation for URI. Options:
- force(Boolean)
- If
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.
- keep(Boolean)
- If
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:
- rdf_register_prefix(+Prefix, +URI) is det
- rdf_register_prefix(+Prefix, +URI, +Options) is det
- Register Prefix as an abbreviation for URI. Options:
- force(Boolean)
- If
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.
- keep(Boolean)
- If
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:
- rdf_meta(+Heads)
- This directive defines the argument types of the named
predicates, which will force compile time namespace expansion
for these predicates. Heads is a coma-separated list of callable
terms. Defined argument properties are:
- :
-
Argument is a goal. The goal is processed using expand_goal/2,
recursively applying goal transformation on the argument.
- +
-
The argument is instantiated at entry. Nothing is changed.
- -
-
The argument is not instantiated at entry. Nothing is changed.
- ?
-
The argument is unbound or instantiated at entry. Nothing is
changed.
- @
-
The argument is not changed.
- r
-
The argument must be a resource. If it is a term
prefix:local it is translated.
- o
-
The argument is an object or resource. See
rdf_global_object/2.
- t
-
The argument is a term that must be translated. Expansion will
translate all occurrences of prefix:local appearing
anywhere in the term. See rdf_global_term/2.
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 explicitly
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
.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
- rdf_prefix_append(Arg1, Arg2, Arg3)
- rdf_prefix_maplist(Arg1, Arg2, Arg3)
- rdf_prefix_maplist(Arg1, Arg2, Arg3, Arg4)
- rdf_equal(Arg1, Arg2)
- rdf_prefix_iri(Arg1, Arg2)
- rdf_prefix_term(Arg1, Arg2)
- rdf_prefix_any(Arg1, Arg2)