Did you know ... Search Documentation:
Pack sparqlprog -- prolog/sparqlprog.pl
PublicShow source

This library provides a prolog interface to SPARQL queries. It allows logic program queries to be compiled to SPARQL, and then executed on a remote SPARQL server.

Quickstart

The following can be entered interactively on the prolog console:

[library(sparqlprog)].
rdf_register_prefix(dbont,'http://dbpedia.org/ontology/').
sparql_endpoint( dbp, 'http://dbpedia.org/sparql/').
dbp ?? rdf(B,rdf:type,dbont:'Band'), rdf(B,dbont:bandMember,M).

This performs the following steps:

  1. For convenience, the prefix dbont is registered using rdf_register_prefix/2
  2. Next we register the short name dbp for the DBPedia endoint using sparql_endpoint/2.
  3. Then we query for all bands and their members using by queried by calling ??/2 - the query is specified using the standard rdf/3 predicate.

On the console the results should look like:

|    dbp ?? rdf(B,rdf:type,dbont:'Band'), rdf(B,dbont:bandMember,M).
B = 'http://dbpedia.org/resource/Alice_in_Chains',
M = 'http://dbpedia.org/resource/Sean_Kinney' ;
B = 'http://dbpedia.org/resource/Alice_in_Chains',
M = 'http://dbpedia.org/resource/William_DuVall' ;
B = 'http://dbpedia.org/resource/Alice_in_Chains',
M = 'http://dbpedia.org/resource/Jerry_Cantrell' ;
B = 'http://dbpedia.org/resource/Alice_in_Chains',
M = 'http://dbpedia.org/resource/Mike_Inez' ;
B = 'http://dbpedia.org/resource/Anthrax_(American_band)',
M = 'http://dbpedia.org/resource/Scott_Ian' .

Using user-defined predicates

You can define your own predicates for use in queries. So long as these stay within the sparqlprog subset, they can be rewritten into a query formed from rdf/3 terms.

For example, you can create a file dbpedia.pl with the following content:

band(X) :- rdf(X,rdf:type,dbont:'Band').
band_member(S,O) :- rdf(S,dbont:bandMember,O).

The original query can then be rewritten as:

dbp ?? band(B), band_member(B,M).

library(sparqlprog/ontologies/dbpedia) provides basic wrapper predicates for dbpedia.

This becomes more advantageous where we want to re-use predicates that encapsulate some query logic, for example, the following 3-ary predicate connects two bands by a shared member:

has_shared_band_member(B1,B2,A) :-
      rdf(A,dbo:associatedBand,B1),
      rdf(A,dbo:associatedBand,B2),
      B1\=B2.

library(sparqlprog/ontologies/dbpedia/dbpedia_matcher) shows how to construct a more advanced example for being able to perform semantic similarity of bands based on shared genres.

sparqlprog is distributed with a number of modules for existing triplestore schemas (with a bias towards life sciences triplestores).

In future some of these will have their own distribution. Some examples:

Note that library(sparqlprog/ontologies/wikidata) is deprecated, instead use library(sparqlprog_wikidata), a separate distribution

using OWL

library(sparqlprog/owl_util) provides predicates for working with OWL ontologies.

For example, owl_edge/4 provides an easy way to extract 'edges' from an ontology (e.g subClassOf between named classes, or involving existential restrictions).

library(sparqlprog/owl_search_viz) provides predicates for searching and visualizing OWL ontologies

sparqlprog language

Any program composed of sparqlprog primitive predicates and the following connectors is considered to be a sparqlprog program, and can be translated to SPARQL.

The connectors allowed are:

  • (,)/2 conjunctive queries
  • (;)/2 disjunctive queries
  • (\+)/1 negation
  • (:-)/2 defining predicates

Note that the cut operator ! is not allowed.

The following are sparqlprog primitives:

Additionally, all SPARQL functions are treated as built-in predicates, e.g. regex/3, str_starts/2, lcase/2

Running sparqlprog programs over in-memory database

SWI-Prolog has its own in-memory database that can be interrogated via rdf/3.

sparqlprog programs can be executed over this in-memory database, as well as remote databases. See sparqlprog/emulate_builtins.pl for examples

Mixing remote and local execution

One of the challenges of using SPARQL with a traditional programming language is the impedance mismatch when combining query logic and programmatic logic. With sparqlprog, both programs and queries are specified in the same language.

Authors

  • Adapted from Samer Abdallah's sparkle by Chris Mungall 2018
  • Samer's code is based on Yves Raimond's swic package, but completely re-written. ...

    @author Samer Abdallah @author Chris Mungall

 ??(?EP, +Goal:sparql_goal, +SelectTerm) is nondet
 ??(?EP, +Goal:sparql_goal, +SelectTerm, +Opts:list) is nondet
Query endpoint EP using Goal, selecting variables in SelectTerm

EP should be a name declared using sparql_endpoint/2. IF EP is unbound on entry, it is bound to the endpoint from which the current bindings were obtained.

Goal is any prolog query that conforms to the sparqlprog subset. i.e. it consists of sparqlprog predicates such as rdf/3, or defined predicates that can be compiled down to basic predicates.

SelectTerm is any prolog term, the variables used in this term will be used to determine the SELECT in the SPARQL query

Example:

??(dbp, band_member(B,M), row([B,M]))

Note in many cases the SELECT variables can be determined from the query in which case ??/2 is more convenient

 ??(?EP, +Goal:sparql_goal) is nondet
Equivalent to ??/3 where the SELECT variables are extracted from variables in Goal.

Note: if Goal contains an aggregate query then ??/3 should be used.

 ??(+Goal:sparql_goal) is nondet
equivalent to ??/2, calling all known endpoints in parallel.
 srule(+Pred, +Args) is det
 srule(+Pred, +Args, +Desc) is det
declare a new sparql rule
 sparql_endpoint(+EP:ground, +URL:atom, +Options) is det
 sparql_endpoint(+EP:ground, +URL:atom) is det
Declares EP as a short name for a SPARQL endpoint with the given URL.

No options are defined at the moment.

Example:

sparql_endpoint( dbp, 'http://dbpedia.org/sparql/').
 current_sparql_endpoint(-EP:ground, -Host:atom, -Port:natural, -Path:atom, -Options:list) is nondet
Succeeds once for each known endpoint.
 create_sparql_select(+SelectTerm, +Goal, -SPARQL, +Opts) is det
 create_sparql_select(+Goal, -SPARQL, +Opts) is det
 create_sparql_select(+Goal, -SPARQL) is det
Generates a sparql SELECT or ASK statement for a prolog goal without executing it.

Goal can be any sparqlprog program, see ??/3

 inject_label_query(+Select, +Query, ?Select2, ?Query2, +Opts) is det
Add an optional(rdf(X,rdfs:label,XL)) for every variable X in Select
 create_sparql_construct(+Head, +Goal, -SPARQL, +Opts) is det
 create_sparql_construct(+Head, +Goal, -SPARQL) is det
Generates a sparql CONSTRUCT statement for a prolog goal without executing it.

Goal or Head can be any prolog goal consisting of based rdf/3 or rdf/4 statements, filters, or terms that can be rewritten in this way

the Head forms the head part of the CONSTRUCT

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 sparql_endpoint(Arg1, Arg2)
 sparql_endpoint_url(Arg1, Arg2)
 srule(Arg1, Arg2, Arg3)
 srule(Arg1, Arg2, Arg3, Arg4)
 create_sparql_select(Arg1, Arg2)
 create_sparql_select(Arg1, Arg2, Arg3)
 create_sparql_construct(Arg1, Arg2, Arg3)
 service_query_all(Arg1, Arg2, Arg3, Arg4)
 service(Arg1, Arg2)
 service(Arg1, Arg2, Arg3)
 ??(Arg1, Arg2, Arg3, Arg4)