rdf_db.pl -- Core RDF database
The file library(semweb/rdf_db) provides the core of the SWI-Prolog RDF store.
- rdf_equal(?Resource1, ?Resource2)
- Simple equality test to exploit goal-expansion.
- lang_equal(+Lang1, +Lang2) is semidet
- True if two RFC language specifiers denote the same language
- lang_matches(+Lang, +Pattern) is semidet
- True if Lang matches Pattern. This implements XML language matching conform RFC 4647. Both Lang and Pattern are dash-separated strings of identifiers or (for Pattern) the wildcard *. Identifiers are matched case-insensitive and a * matches any number of identifiers. A short pattern is the same as *.
- rdf(?Subject, ?Predicate, ?Object) is nondet
- Elementary query for triples. Subject and Predicate are atoms
representing the fully qualified URL of the resource. Object is
either an atom representing a resource or
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:- Atom
- If the value is a simple atom it is the textual representation of a string literal without explicit type or language qualifier.
- lang(LangID, Atom)
- Atom represents the text of a string literal qualified with the given language.
- type(TypeID, Value)
- Used for attributes qualified using the
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.- plain(+Text)
- Perform exact match and demand the language or type qualifiers to match. This query is fully indexed.
- icase(+Text)
- Perform a full but case-insensitive match. This query is fully indexed.
- exact(+Text)
- Same as
icase(Text)
. Backward compatibility. - substring(+Text)
- Match any literal that contains Text as a case-insensitive substring. The query is not indexed on Object.
- word(+Text)
- Match any literal that contains Text delimited by a non alpha-numeric character, the start or end of the string. The query is not indexed on Object.
- prefix(+Text)
- Match any literal that starts with Text. This call is intended for completion. The query is indexed using the skip list of literals.
- ge(+Literal)
- Match any literal that is equal or larger than Literal in the ordered set of literals.
- gt(+Literal)
- Match any literal that is larger than Literal in the ordered set of literals.
- eq(+Literal)
- Match any literal that is equal to Literal in the ordered set of literals.
- le(+Literal)
- Match any literal that is equal or smaller than Literal in the ordered set of literals.
- lt(+Literal)
- Match any literal that is smaller than Literal in the ordered set of literals.
- between(+Literal1, +Literal2)
- Match any literal that is between Literal1 and Literal2 in the ordered set of literals. This may include both Literal1 and Literal2.
- like(+Pattern)
- Match any literal that matches Pattern case insensitively, where the `*' character in Pattern matches zero or more characters.
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 likerdf(S,P,O)
,rdf(O,P2,O2)
to proceed without errors. - rdf(?Subject, ?Predicate, ?Object, ?Source) is nondet
- As rdf/3 but in addition query the graph to which the triple belongs. Unlike rdf/3, this predicate does not remove duplicates from the result set.
- rdf_has(?Subject, +Predicate, ?Object) is nondet
- Succeeds if the triple
rdf(Subject, Predicate, Object)
is true exploiting the rdfs:subPropertyOf predicate as well as inverse predicates declared using rdf_set_predicate/2 with theinverse_of
property. - rdf_has(?Subject, +Predicate, ?Object, -RealPredicate) is nondet
- Same as rdf_has/3, but RealPredicate is unified to the actual
predicate that makes this relation true. RealPredicate must be
Predicate or an rdfs:subPropertyOf Predicate. If an inverse
match is found, RealPredicate is the term
inverse_of(Pred)
. - rdf_reachable(?Subject, +Predicate, ?Object) is nondet
- Is true if Object can be reached from Subject following the
transitive predicate Predicate or a sub-property thereof, while
repecting the
symetric(true)
orinverse_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' ; ...
- rdf_reachable(?Subject, +Predicate, ?Object, +MaxD, -D) is nondet
- Same as rdf_reachable/3, but in addition, MaxD limits the number
of edges expanded and D is unified with the `distance' between
Subject and Object. Distance 0 means Subject and Object are the
same resource. MaxD can be the constant
infinite
to impose no distance-limit. - rdf_subject(?Resource) is nondet
- True if Resource appears as a subject. This query respects the visibility rules implied by the logical update view.
- rdf_resource(?Resource) is nondet
- True when Resource is a resource used as a subject or object in
a triple.
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.
- rdf_assert(+Subject, +Predicate, +Object) is det
- Assert a new triple into the database. This is equivalent to
rdf_assert/4 using Graph
user
. Subject and Predicate are resources. Object is either a resource or a termliteral(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. - rdf_assert(+Subject, +Predicate, +Object, +Graph) is det
- As rdf_assert/3, adding the predicate to the indicated named graph.
- rdf_retractall(?Subject, ?Predicate, ?Object) is det
- Remove all matching triples from the database. As rdf_retractall/4 using an unbound graph.
- rdf_retractall(?Subject, ?Predicate, ?Object, ?Graph) is det
- As rdf_retractall/3, also matching Graph. This is particulary useful to remove all triples coming from a loaded file. See also rdf_unload/1.
- rdf_update(+Subject, +Predicate, +Object, ++Action) is det
- rdf_update(+Subject, +Predicate, +Object, +Graph, ++Action) is det
- Replaces one of the three (four) fields on the matching triples
depending on Action:
- subject(Resource)
- Changes the first field of the triple.
- predicate(Resource)
- Changes the second field of the triple.
- object(Object)
- Changes the last field of the triple to the given resource or
literal(Value)
. - graph(Graph)
- Moves the triple from its current named graph to Graph. This only works with rdf_update/5 and throws an error when used with rdf_update/4.
- rdf_member_property(?Prop, ?Index)
- Deal with the rdf:_1, ... properties.
- rdf_node(-Id)
- Generate a unique blank node identifier for a subject.
- rdf_bnode(-Id)
- Generate a unique anonymous identifier for a subject.
- rdf_is_bnode(+Id)
- Tests if a resource is a blank node (i.e. is an anonymous
resource). A blank node is represented as an atom that starts
with
_:
. For backward compatibility reason,__
is also considered to be a blank node. - rdf_is_resource(@Term) is semidet
- True if Term is an RDF resource. Note that this is merely a type-test; it does not mean this resource is involved in any triple. Blank nodes are also considered resources.
- rdf_is_literal(@Term) is semidet
- True if Term is an RDF literal object. Currently only checks for groundness and the literal functor.
- rdf_current_literal(-Literal) is nondet
- True when Literal is a currently known literal. Enumerates each unique literal exactly once. Note that it is possible that the literal only appears in already deleted triples. Deleted triples may be locked due to active queries, transactions or snapshots or may not yet be reclaimed by the garbage collector.
- rdf_literal_value(+Literal, -Value) is semidet
- True when value is the appropriate Prolog representation of
Literal in the RDF value space. Current mapping:
Plain literals Atom Language tagged literal Atom holding plain text xsd:string Atom rdf:XMLLiteral XML DOM Tree Numeric XSD type Number - rdf_source_location(+Subject, -Location) is nondet
- True when triples for Subject are loaded from Location.
- rdf_gc is det
- Run the RDF-DB garbage collector until no garbage is left and all
tables are fully optimized. Under normal operation a separate thread
with identifier
__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.
- rdf_statistics(?KeyValue) is nondet
- Obtain statistics on the RDF database. Defined statistics are:
- graphs(-Count)
- Number of named graphs.
- triples(-Count)
- Total number of triples in the database. This is the number of asserted triples minus the number of retracted ones. The number of visible triples in a particular context may be different due to visibility rules defined by the logical update view and transaction isolation.
- resources(-Count)
- Number of resources that appear as subject or object in a triple. See rdf_resource/1.
- properties(-Count)
- Number of current predicates. See rdf_current_predicate/1.
- literals(-Count)
- Number of current literals. See rdf_current_literal/1.
- gc(GCCount, ReclaimedTriples, ReindexedTriples, Time)
- Information about the garbage collector.
- searched_nodes(-Count)
- Number of nodes expanded by rdf_reachable/3 and rdf_reachable/5.
- lookup(rdf(S, P, O, G), Count)
- Number of queries that have been performed for this particular instantiation pattern. Each of S,P,O,G is either + or -. Fails in case the number of performed queries is zero.
- hash_quality(rdf(S, P, O, G), Buckets, Quality, PendingResize)
- Statistics on the index for this pattern. Indices are created lazily on the first relevant query.
- triples_by_graph(Graph, Count)
- This statistics is produced for each named graph. See
triples
for the interpretation of this value.
- rdf_current_predicate(?Predicate) is nondet
- True when Predicate is a currently known predicate. Predicates
are created if a triples is created that uses this predicate or
a property of the predicate is set using rdf_set_predicate/2.
The predicate may (no longer) have triples associated with it.
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. - rdf_predicate_property(?Predicate, ?Property)
- Query properties of a defined predicate. Currently defined
properties are given below.
- symmetric(Bool)
- True if the predicate is defined to be symetric. I.e., {A} P
{B} implies {B} P {A}. Setting symmetric is equivalent to
inverse_of(Self)
. - inverse_of(Inverse)
- True if this predicate is the inverse of Inverse. This property is used by rdf_has/3, rdf_has/4, rdf_reachable/3 and rdf_reachable/5.
- transitive(Bool)
- True if this predicate is transitive. This predicate is currently not used. It might be used to make rdf_has/3 imply rdf_reachable/3 for transitive predicates.
- triples(Triples)
- Unify Triples with the number of existing triples using this predicate as second argument. Reporting the number of triples is intended to support query optimization.
- rdf_subject_branch_factor(-Float)
- Unify Float with the average number of triples associated with each unique value for the subject-side of this relation. If there are no triples the value 0.0 is returned. This value is cached with the predicate and recomputed only after substantial changes to the triple set associated to this relation. This property is intended for path optimalisation when solving conjunctions of rdf/3 goals.
- rdf_object_branch_factor(-Float)
- Unify Float with the average number of triples associated with
each unique value for the object-side of this relation. In
addition to the comments with the
rdf_subject_branch_factor
property, uniqueness of the object value is computed from the hash key rather than the actual values. - rdfs_subject_branch_factor(-Float)
- Same as
rdf_subject_branch_factor
, but also considering triples of `subPropertyOf' this relation. See also rdf_has/3. - rdfs_object_branch_factor(-Float)
- Same as
rdf_object_branch_factor
, but also considering triples of `subPropertyOf' this relation. See also rdf_has/3.
- rdf_set_predicate(+Predicate, +Property) is det
- Define a property of the predicate. This predicate currently
supports the following properties:
- symmetric(+Boolean)
- Set/unset the predicate as being symmetric. Using
symmetric(true)
is the same asinverse_of(Predicate)
, i.e., creating a predicate that is the inverse of itself. - transitive(+Boolean)
- Sets the transitive property.
- inverse_of(+Predicate2)
- Define Predicate as the inverse of Predicate2. An inverse
relation is deleted using
inverse_of([])
.
The
transitive
property is currently not used. Thesymmetric
andinverse_of
properties are considered by rdf_has/3,4 and rdf_reachable/3. - rdf_snapshot(-Snapshot) is det
- Take a snapshot of the current state of the RDF store. Later,
goals may be executed in the context of the database at this
moment using rdf_transaction/3 with the
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_delete_snapshot(+Snapshot) is det
- Delete a snapshot as obtained from rdf_snapshot/1. After this call, resources used for maintaining the snapshot become subject to garbage collection.
- rdf_current_snapshot(?Term) is nondet
- True when Term is a currently known snapshot.
- rdf_transaction(:Goal) is semidet
- Same as
rdf_transaction(Goal, user, [])
. See rdf_transaction/3. - rdf_transaction(:Goal, +Id) is semidet
- Same as
rdf_transaction(Goal, Id, [])
. See rdf_transaction/3. - rdf_transaction(:Goal, +Id, +Options) is semidet
- Run Goal in an RDF transaction. Compared to the ACID model,
RDF transactions have the following properties:
- Modifications inside the transactions become all atomically visible to the outside world if Goal succeeds or remain invisible if Goal fails or throws an exception. I.e., the atomicy property is fully supported.
- Consistency is not guaranteed. Later versions may implement consistency constraints that will be checked serialized just before the actual commit of a transaction.
- Concurrently executing transactions do not infuence each other. I.e., the isolation property is fully supported.
- Durability can be activated by loading library(semweb/rdf_persistency).
Processed options are:
- snapshot(+Snapshot)
- Execute Goal using the state of the RDF store as stored in
Snapshot. See rdf_snapshot/1. Snapshot can also be the
atom
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.
- rdf_active_transaction(?Id) is nondet
- True if Id is the identifier of a transaction in the context of which this call is executed. If Id is not instantiated, backtracking yields transaction identifiers starting with the innermost nested transaction. Transaction identifier terms are not copied, need not be ground and can be instantiated during the transaction.
- rdf_monitor(:Goal, +Options)
- Call Goal if specified actions occur on the database.
- rdf_warm_indexes
- Warm all indexes. See rdf_warm_indexes/1.
- rdf_warm_indexes(+Indexes) is det
- Create the named indexes. Normally, the RDF database creates indexes on lazily the first time they are needed. This predicate serves two purposes: it provides an explicit way to make sure that the required indexes are present and creating multiple indexes at the same time is more efficient.
- rdf_update_duplicates is det
- Update the duplicate administration of the RDF store. This marks
every triple that is potentionally a duplicate of another as
duplicate. Being potentially a duplicate means that subject,
predicate and object are equivalent and the life-times of the
two triples overlap.
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.
- rdf_update_duplicates is det
- Update the duplicate administration. If this adminstration is
up-to-date, each triples that may have a duplicate is flagged.
The predicate rdf/3 uses this administration to speedup checking
for duplicate answers.
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_save_db(+File) is det
- rdf_save_db(+File, +Graph) is det
- Save triples into File in a quick-to-load binary format. If Graph is supplied only triples flagged to originate from that database are added. Files created this way can be loaded using rdf_load_db/1.
- rdf_load_db(+File) is det
- Load triples from a file created using rdf_save_db/2.
- rdf_load(+FileOrList) is det
- Same as
rdf_load(FileOrList, [])
. See rdf_load/2. - rdf_load(+FileOrList, :Options) is det
- Load RDF data. Options provides additional processing options.
Defined options are:
- blank_nodes(+ShareMode)
- How to handle equivalent blank nodes. If
share
(default), equivalent blank nodes are shared in the same resource. - base_uri(+URI)
- URI that is used for rdf:about="" and other RDF constructs that are relative to the base uri. Default is the source URL.
- concurrent(+Jobs)
- If FileOrList is a list of files, process the input files using Jobs threads concurrently. Default is the mininum of the number of cores and the number of inputs. Higher values can be useful when loading inputs from (slow) network connections. Using 1 (one) does not use separate worker threads.
- format(+Format)
- Specify the source format explicitly. Normally this is deduced from the filename extension or the mime-type. The core library understands the formats xml (RDF/XML) and triples (internal quick load and cache format). Plugins, such as library(semweb/turtle) extend the set of recognised extensions.
- graph(?Graph)
- Named graph in which to load the data. It is not allowed
to load two sources into the same named graph. If Graph is
unbound, it is unified to the graph into which the data is
loaded. The default graph is a
file://
URL when loading a file or, if the specification is a URL, its normalized version without the optional #fragment. - if(Condition)
- When to load the file. One of
true
,changed
(default) ornot_loaded
. - modified(-Modified)
- Unify Modified with one of
not_modified
,cached(File)
,last_modified(Stamp)
orunknown
. - cache(Bool)
- If
false
, do not use or create a cache file. - register_namespaces(Bool)
- If
true
(defaultfalse
), registerxmlns
namespace declarations or Turtle@prefix
prefixes using rdf_register_prefix/3 if there is no conflict. - silent(+Bool)
- If
true
, the message reporting completion is printed using levelsilent
. Otherwise the level isinformational
. See also print_message/2. - prefixes(-Prefixes)
- Returns the prefixes defined in the source data file as a list of pairs.
- multifile +Boolean
- Indicate that the addressed graph may be populated with triples from multiple sources. This disables caching and avoids that an rdf_load/2 call affecting the specified graph cleans the graph.
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)).
- rdf_file_type(+Extension, -Format) is semidet[multifile]
- True if Format is the format belonging to the given file extension. This predicate is multifile and can thus be extended by plugins.
- rdf_load_stream(+Format, +Stream, :Options)[multifile]
- Load RDF data from Stream.
- rdf_unload(+Source) is det
- Identify the graph loaded from Source and use rdf_unload_graph/1 to erase this graph.
- rdf_unload_graph(+Graph) is det
- Remove Graph from the RDF store. Succeeds silently if the named graph does not exist.
- rdf_create_graph(+Graph) is det
- Create an RDF graph without triples. Succeeds silently if the graph already exists.
- rdf_graph(?Graph) is nondet
- True when Graph is an existing graph.
- rdf_source(?Graph, ?SourceURL) is nondet
- True if named Graph is loaded from SourceURL.
- rdf_source(?Source)
- True if Source is a loaded source.
- rdf_make
- Reload all loaded files that have been modified since the last time they were loaded.
- rdf_graph_property(?Graph, ?Property) is nondet
- True when Property is a property of Graph. Defined properties
are:
- hash(Hash)
- Hash is the (MD5-)hash for the content of Graph.
- modified(Boolean)
- True if the graph is modified since it was loaded or
rdf_set_graph/2 was called with
modified(false)
. - source(Source)
- The graph is loaded from the Source (a URL)
- source_last_modified(?Time)
- Time is the last-modified timestamp of Source at the moment the graph was loaded from Source.
- triples(Count)
- True when Count is the number of triples in Graph.
Additional graph properties can be added by defining rules for the multifile predicate property_of_graph/2. Currently, the following extensions are defined:
- library(semweb/rdf_persistency)
- persistent(Boolean)
- Boolean is
true
if the graph is persistent.
- rdf_set_graph(+Graph, +Property) is det
- Set properties of Graph. Defined properties are:
- modified(false)
- Set the modified state of Graph to false.
- rdf_reset_db
- Remove all triples from the RDF database and reset all its statistics.
- rdf_save(+Out) is det
- Same as
rdf_save(Out, [])
. See rdf_save/2 for details. - rdf_save(+Out, :Options) is det
- Write RDF data as RDF/XML. Options is a list of one or more of
the following options:
- graph(+Graph)
- Save only triples associated to the given named Graph.
- anon(Bool)
- If
false
(defaulttrue
) do not save blank nodes that do not appear (indirectly) as object of a named resource. - base_uri(URI)
- BaseURI used. If present, all URIs that can be
represented relative to this base are written using
their shorthand. See also
write_xml_base
option. - convert_typed_literal(:Convertor)
- Call Convertor(-Type, -Content, +RDFObject), providing the opposite for the convert_typed_literal option of the RDF parser.
- document_language(+Lang)
- Initial
xml:lang
saved with rdf:RDF element. - encoding(Encoding)
- Encoding for the output. Either utf8 or iso_latin_1.
- inline(+Bool)
- If
true
(defaultfalse
), inline resources when encountered for the first time. Normally, only bnodes are handled this way. - namespaces(+List)
- Explicitly specify saved namespace declarations. See rdf_save_header/2 option namespaces for details.
- sorted(+Boolean)
- If
true
(defaultfalse
), emit subjects sorted on the full URI. Useful to make file comparison easier. - write_xml_base(Bool)
- If
false
, do not include thexml:base
declaration that is written normally when using thebase_uri
option. - xml_attributes(+Bool)
- If
false
(defaulttrue
), never use xml attributes to save plain literal attributes, i.e., always used an XML element as in<name>Joe</name>
.
- rdf_save_header(+Fd, +Options)
- Save XML document header, doctype and open the RDF environment.
This predicate also sets up the namespace notation.
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:
- graph(+URI)
- Only search for namespaces used in triples that belong to the given named graph.
- namespaces(+List)
- Where List is a list of namespace abbreviations. With this
option, the expensive search for all namespaces that may be
used by your data is omitted. The namespaces
rdf
andrdfs
are added to the provided List. If a namespace is not declared, the resource is emitted in non-abreviated form.
- rdf_graph_prefixes(?Graph, -List:ord_set) is det
- rdf_graph_prefixes(?Graph, -List:ord_set, :Options) is det
- List is a sorted list of prefixes (namepaces) in Graph. Options
defined are:
- filter(:Filter)
- optional Filter argument is used to filter the results. It
is called with 3 additional arguments:
call(Filter, Where, Prefix, URI)
The Where argument gives the location of the prefix ans is one of
subject
,predicate
,object
ortype
. The Prefix argument is the potentionally new prefix and URI is the full URI that is being processed. - expand(:Goal)
- Hook to generate the graph. Called using
call(Goal,S,P,O,Graph)
- min_count(+Count)
- Only include prefixes that appear at least N times. Default is 1. Declared prefixes are always returned if found at least one time.
- get_prefix(:GetPrefix)
- Predicate to extract the candidate prefix from an IRI. Default is iri_xml_namespace/2.
- rdf_save_footer(Out:stream) is det
- Finish XML generation and write the document footer.
- rdf_save_subject(+Out, +Subject:resource, +Options) is det
- Save the triples associated to Subject to Out. Options:
- graph(+Graph)
- Only save properties from Graph.
- base_uri(+URI)
- convert_typed_literal(:Goal)
- document_language(+XMLLang)
- rdf_compare(-Dif, +Object1, +Object2) is det
- Compare two object terms. Where SPARQL defines a partial
ordering, we define a complete ordering of terms. The ordering
is defines as:
- Blank nodes < IRIs < Literals
- Numeric literals < other literals
- Numeric literals are compared by value and then by type, where Integer < Decimal < Double
- Other literals are compare lexically, case insensitive. If equal, uppercase preceeds lowercase. If still equal, the types are compared lexically.
- rdf_match_label(+How, +Pattern, +Label) is semidet
- True if Label matches Pattern according to How. How is one of
icase
,substring
,word
,prefix
orlike
. For backward compatibility,exact
is a synonym foricase
. - rdf_split_url(+Prefix, +Local, -URL) is det
- rdf_split_url(-Prefix, -Local, +URL) is det
- Split/join a URL. This functionality is moved to library(sgml).
- rdf_url_namespace(+URL, -Namespace)
- Namespace is the namespace of URL.
- rdf_new_literal_map(-Map) is det
- Create a new literal map, returning an opaque handle.
- rdf_destroy_literal_map(+Map) is det
- Destroy a literal map. After this call, further use of the Map handle is illegal. Additional synchronisation is needed if maps that are shared between threads are destroyed to guarantee the handle is no longer used. In some scenarios rdf_reset_literal_map/1 provides a safe alternative.
- rdf_reset_literal_map(+Map) is det
- Delete all content from the literal map.
- rdf_insert_literal_map(+Map, +Key, +Value) is det
- Add a relation between Key and Value to the map. If this relation already exists no action is performed.
- rdf_insert_literal_map(+Map, +Key, +Value, -KeyCount) is det
- As rdf_insert_literal_map/3. In addition, if Key is a new key in Map, unify KeyCount with the number of keys in Map. This serves two purposes. Derived maps, such as the stem and metaphone maps need to know about new keys and it avoids additional foreign calls for doing the progress in rdf_litindex.pl.
- rdf_delete_literal_map(+Map, +Key) is det
- Delete Key and all associated values from the map.
- rdf_delete_literal_map(+Map, +Key, +Value) is det
- Delete the association between Key and Value from the map.
- rdf_find_literal_map(+Map, +KeyList, -ValueList) is det
- Unify ValueList with an ordered set of values associated to all
keys from KeyList. Each key in KeyList is either an atom, an
integer or a term
not(Key)
. If not-terms are provided, there must be at least one positive keywords. The negations are tested after establishing the positive matches. - rdf_keys_in_literal_map(+Map, +Spec, -Answer) is det
- Realises various queries on the key-set:
- all Unify Answer with an ordered list of all keys.
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).
- rdf_statistics_literal_map(+Map, -KeyValue)
- Query some statistics of the map. Provides KeyValue are:
- size(-Keys, -Relations)
- Unify Keys with the total key-count of the index and Relation with the total Key-Value count.
- rdf_version(-Version) is det
- True when Version is the numerical version-id of this library.
The version is computed as
Major*10000 + Minor*100 + Patch.
- rdf_set(+Term) is det
- Set properties of the RDF store. Currently defines:
- hash(+Hash, +Parameter, +Value)
- Set properties for a triple index. Hash is one of
s
,p
,sp
,o
,po
,spo
,g
,sg
orpg
. Parameter is one of:- size
- Value defines the number of entries in the hash-table.
Value is rounded down to a power of 2. After setting
the size explicitly, auto-sizing for this table is
disabled. Setting the size smaller than the current
size results in a
permission_error
exception. - average_chain_len
- Set maximum average collision number for the hash.
- optimize_threshold
- Related to resizing hash-tables. If 0, all triples are moved to the new size by the garbage collector. If more then zero, those of the last Value resize steps remain at their current location. Leaving cells at their current location reduces memory fragmentation and slows down access.
- rdf_md5(+Graph, -MD5) is det
- True when MD5 is the MD5 hash for all triples in graph. The MD5 digest itself is represented as an atom holding a 32-character hexadecimal string. The library maintains the digest incrementally on rdf_load/[1,2], rdf_load_db/1, rdf_assert/[3,4] and rdf_retractall/[3,4]. Checking whether the digest has changed since the last rdf_load/[1,2] call provides a practical means for checking whether the file needs to be saved.
- rdf_generation(-Generation) is det
- True when Generation is the current generation of the database.
Each modification to the database increments the generation. It
can be used to check the validity of cached results deduced from
the database. Committing a non-empty transaction increments the
generation by one.
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.
- rdf_estimate_complexity(?Subject, ?Predicate, ?Object, -Complexity)
- Return the number of alternatives as indicated by the database internal hashed indexing. This is a rough measure for the number of alternatives we can expect for an rdf_has/3 call using the given three arguments. When called with three variables, the total number of triples is returned. This estimate is used in query optimisation. See also rdf_predicate_property/2 and rdf_statistics/1 for additional information to help optimizers.
- rdf_debug(+Level) is det
- Set debugging to Level. Level is an integer 0..9. Default is 0 no debugging.
- rdf_atom_md5(+Text, +Times, -MD5) is det
- Computes the MD5 hash from Text, which is an atom, string or list of character codes. Times is an integer >= 1. When > 0, the MD5 algorithm is repeated Times times on the generated hash. This can be used for password encryption algorithms to make generate-and-test loops slow.
Re-exported predicates
The following predicates are re-exported from other modules
- rdf_global_object(+Object, :GlobalObject) is semidet
- rdf_global_object(-Object, :GlobalObject) is semidet
- Same as rdf_global_id/2, but intended for dealing with the object part of a triple, in particular the type for typed literals. Note that the predicate is a meta-predicate on the output argument. This is necessary to get the module context while the first argument may be of the form (:)/2.
- rdf_current_ns(:Prefix, ?URI) is nondet
- rdf_current_prefix(:Alias, ?URI) is nondet
- Query predefined prefixes and prefixes defined with
rdf_register_prefix/2 and local prefixes defined with
rdf_prefix/2. If Alias is unbound and one URI is the prefix of
another, the longest is returned first. This allows turning a
resource into a prefix/local couple using the simple enumeration
below. See rdf_global_id/2.
rdf_current_prefix(Prefix, Expansion), atom_concat(Expansion, Local, URI),
- 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 occurences 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 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 termPrefix:Local
) implies that simple operations such as comparison of IRIs no longer map to native Prolog operations such asIRI1 == IRI2
. - rdf_unregister_prefix(+Alias) is det
- Delete a prefix global registration.
- rdf_global_id(?IRISpec, :IRI) is semidet
- Convert between Prefix:Local and full IRI (an atom). If IRISpec is
an atom, it is simply unified with IRI. This predicate fails
silently if IRI is an RDF literal.
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_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_ns(:Prefix, ?URI) is det
- rdf_register_ns(:Prefix, ?URI, +Options) is det
- Register an RDF prefix.
- 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_global_term(+TermIn, :GlobalTerm) is det
- Performs rdf_global_id/2 on predixed IRIs and rdf_global_object/2 on
RDF literals, by recursively analysing the term. Note that the
predicate is a meta-predicate on the output argument. This is
necessary to get the module context while the first argument may be
of the form (:)/2.
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. - rdf_register_ns(:Prefix, ?URI) is det
- rdf_register_ns(:Prefix, ?URI, +Options) is det
- Register an RDF prefix.
- 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:
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.