Did you know ... | Search Documentation: |
Pack sparqlprog -- prolog/sparqlprog.pl |
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.
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:
dbont
is registered using rdf_register_prefix/2dbp
for the DBPedia endoint using sparql_endpoint/2.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' .
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:
library(sparqlprog/ontologies/faldo)
, genome locations e.g. location/5library(sparqlprog/ontologies/ebi)
, EBI RDF e.g. homologous_to/2library(sparqlprog/ontologies/biopax3)
, BioPax level 3 e.g. nextStep/2library(sparqlprog/ontologies/disgenet)
, DisGeNet e.g. disease/1, gda/3library(sparqlprog/ontologies/chembl)
, e.g. has_molecule/2library(sparqlprog/ontologies/nextprot)
, e.g. expression/2library(sparqlprog/ontologies/rhea)
, e.g. reaction_chebi_participant/2library(sparqlprog/ontologies/uniprot)
, e.g. protein/1, has_disease_annotation/2.
Note that library(sparqlprog/ontologies/wikidata)
is deprecated, instead use library(sparqlprog_wikidata)
, a separate distribution
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
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:
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
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
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.
@author Samer Abdallah @author Chris Mungall
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
Note: if Goal contains an aggregate query then ??/3 should be used.
No options are defined at the moment.
Example:
sparql_endpoint( dbp, 'http://dbpedia.org/sparql/').
Goal can be any sparqlprog program, see ??/3
optional(rdf(X,rdfs:label,XL))
for every variable X in SelectGoal 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
The following predicates are exported, but not or incorrectly documented.