predicates for querying wikidata using logic predicates

Note: this module uses macros to generate predicates. When this is viewed online using pldoc, the actual predicates will not be visible.

To see the full list of predicates, see pname_wid/3 and cname_wid/3 which declares properties and classes. For each declaration, predicates will be generated. See the README for more details.

*/

   12:- module(sparqlprog_wikidata,
   13          [
   14
   15           property_constraint_pv/4,
   16           
   17           var_drug_condition/4,
   18           
   19           enlabel/2,
   20           enlabelp/2,
   21           enlabel_any/2,
   22           en_alt_label/2,
   23           en_description/2,
   24
   25           subont/3,
   26           extract_subontology/2,
   27
   28           entity_search/2,
   29           entity_search/3,
   30           exact_match/2,
   31           entailed_instance_of_name/2,
   32           instance_of_name/2,
   33
   34           population_at/3,
   35           in_time_interval/3,
   36           geolocation/5,
   37           geolocation/4,
   38           geolocation/3,
   39           coordinate_location_node/2,
   40           node_geolocation/5,
   41           node_geolocation/4,
   42           node_geolocation/3,
   43
   44           geolocation_around/3
   45
   46           ]).   47
   48:- use_module(library(sparqlprog)).   49:- use_module(library(semweb/rdf11)).   50:- use_module(library(sparqlprog/ontologies/owl), [label/2]).   51
   52:- sparql_endpoint( wd, 'http://query.wikidata.org/sparql').   53
   54:- rdf_register_prefix(skos, 'http://www.w3.org/2004/02/skos/core#').   55:- rdf_register_prefix(foaf,'http://xmlns.com/foaf/0.1/').   56:- rdf_register_prefix(dbont,'http://dbpedia.org/ontology/').   57:- rdf_register_prefix(wikipathways,'http://vocabularies.wikipathways.org/wp#').   58:- rdf_register_prefix(obo,'http://purl.obolibrary.org/obo/').   59:- rdf_register_prefix(so,'http://purl.obolibrary.org/obo/SO_').   60
   61% https://www.mediawiki.org/wiki/Wikibase/Indexing/RDF_Dump_Format#Prefixes_used
   62:- rdf_register_prefix(wd,'http://www.wikidata.org/entity/').   63:- rdf_register_prefix(wdt,'http://www.wikidata.org/prop/direct/').   64:- rdf_register_prefix(wbont,'http://wikiba.se/ontology#').   65:- rdf_register_prefix(wikibase,'http://wikiba.se/ontology#').   66:- rdf_register_prefix(bd,'http://www.bigdata.com/rdf#').   67:- rdf_register_prefix(mwapi, 'https://www.mediawiki.org/ontology#API/').   68
   69:- rdf_register_prefix(instance_of,'http://www.wikidata.org/prop/direct/P31').   70
   71:- dynamic pred_info/3.   72
   73% auto-generate predicates for properties
   74user:term_expansion(pname_wid(Module,P,Id),
   75                    [(   Head :- Body),
   76                     (   Head_trans :- Body_trans),
   77                     (   Head_s :- Body_s),
   78                     (   Head_ps :- Body_ps),
   79                     (   Head_psv :- Body_psv),
   80                     (   Head_q :- Body_q),
   81                     (   Head_iri :- true),
   82                     (   Head_eiri :- true),
   83                     (   :- initialization(export(P_trans/2), now)),
   84                     (   :- initialization(export(P_s/2), now)),
   85                     (   :- initialization(export(P_ps/2), now)),
   86                     (   :- initialization(export(P_psv/2), now)),
   87                     (   :- initialization(export(P_q/2), now)),
   88                     (   :- initialization(export(P_iri/1), now)),
   89                     (   :- initialization(export(P_eiri/1), now)),
   90                     (   :- initialization(export(P/2), now))
   91                    ]) :-
   92
   93        % e.g. p9 ==> P9
   94        upcase_atom(Id,Frag),
   95        
   96        
   97        % Truthy assertions about the data, links entity to value directly
   98        % wd:Q2  wdt:P9 <http://acme.com/> ==> P9(Q2,"...")
   99        Head =.. [P,S,O],
  100        atom_concat('http://www.wikidata.org/prop/direct/',Frag,Px),
  101        Body = rdf(S,Px,O),
  102        assert(pred_info(P/2,Module,Px,'asserted triple')),
  103
  104        atom_concat(P,'_transitive',P_trans),
  105        Head_trans =.. [P_trans,S,O],
  106        Body_trans = rdf_path(S,zeroOrMore(Px),O),
  107        assert(pred_info(P/2,Module,triple)),
  108        assert(pred_info(P/2,Module,Px,'inferred triple')),
  109        
  110        
  111        % p: Links entity to statement
  112        % wd:Q2 p:P9 wds:Q2-82a6e009 ==> P9_statement(Q2,wds:....)
  113        atom_concat(P,'_e2s',P_s),
  114        Head_s =.. [P_s,S,O],
  115        atom_concat('http://www.wikidata.org/prop/',Frag,Px_s),
  116        Body_s = rdf(S,Px_s,O),
  117
  118        atom_concat(P,'_iri',P_iri),
  119        Head_iri =.. [P_iri,Px],
  120
  121        atom_concat('http://www.wikidata.org/entity/',Frag,Pe),        
  122        atom_concat(P,'_eiri',P_eiri),
  123        Head_eiri =.. [P_eiri,Pe],
  124        
  125        % ps: Links value from statement
  126        % wds:Q3-24bf3704-4c5d-083a-9b59-1881f82b6b37 ps:P8 "-13000000000-01-01T00:00:00Z"^^xsd:dateTime
  127        atom_concat(P,'_s2v',P_ps),
  128        Head_ps =.. [P_ps,S,O],
  129        atom_concat('http://www.wikidata.org/prop/statement/',Frag,Px_ps),
  130        Body_ps = rdf(S,Px_ps,O),
  131
  132        % psv: 
  133        atom_concat(P,'_psv',P_psv),
  134        Head_psv =.. [P_psv,S,O],
  135        atom_concat('http://www.wikidata.org/prop/statement/value/',Frag,Px_psv),
  136        Body_psv = rdf(S,Px_psv,O),
  137        
  138        % pq: Links qualifier from statement node
  139        % wds:Q3-24bf3704-4c5d-083a-9b59-1881f82b6b37 pq:P8 "-13000000000-01-01T00:00:00Z"^^xsd:dateTime
  140        % => P8_q(wds:..., "..."^^...)
  141        atom_concat(P,'_s2q',P_q),
  142        Head_q =.. [P_q,S,O],
  143        atom_concat('http://www.wikidata.org/prop/qualifier/',Frag,Px_q),
  144        Body_q = rdf(S,Px_q,O).
  145
  146
  147% auto-generate predicates for classes
  148user:term_expansion(cname_wid(Module,C,Id),
  149                    [Rule,
  150                     %RuleInf,
  151                     RuleDirect,
  152                     RuleIsa,
  153                     (   Head_iri :- true),
  154                     (:- initialization(export(C_direct/1), now)),
  155                     %(:- initialization(export(InfC/1), now)),
  156                     (:- initialization(export(SubC/1), now)),
  157                     (:- initialization(export(C_iri/1), now)),
  158                     (:- initialization(export(C/1), now))
  159                     ]) :-
  160        upcase_atom(Id,Frag),
  161        atom_concat('http://www.wikidata.org/entity/',Frag,Cx),
  162        
  163        Head =.. [C,I],
  164        Body = rdf(I,('http://www.wikidata.org/prop/direct/P31'/zeroOrMore('http://www.wikidata.org/prop/direct/P279')),Cx),
  165        Rule = (Head :- Body),
  166        assert(pred_info(C/1, Module, instance)),
  167
  168        atom_concat(C,'_direct',C_direct),
  169        HeadD =.. [C_direct,I],
  170        BodyD = rdf(I,'http://www.wikidata.org/prop/direct/P31',Cx),
  171        RuleDirect = (HeadD :- BodyD),
  172
  173        atom_concat(C,'_iri',C_iri),
  174        Head_iri =.. [C_iri,Cx],
  175        
  176        %atom_concat(C,'_inf',InfC),
  177        %Head2 =.. [InfC,I],
  178        %Body2 = rdf(I,('http://www.wikidata.org/prop/direct/P31'/zeroOrMore('http://www.wikidata.org/prop/direct/P279')),Cx),
  179        %RuleInf = (Head2 :- Body2),
  180        
  181        atom_concat('isa_',C,SubC),
  182        Head3 =.. [SubC,I],
  183        Body3 = rdf(I,zeroOrMore('http://www.wikidata.org/prop/direct/P279'),Cx),
  184        RuleIsa = (Head3 :- Body3).
 subont(+QueryCls, ?SubClass, ?SuperClass) is nondet
given a query class find all SubClassOf axioms in the sub-ontology defined by any ancestor or decendant of QueryCls
  190subont(C,A,B) :-
  191        subclass_of_transitive(C,A),subclass_of(A,B).
  192subont(C,A,B) :-
  193        subclass_of_transitive(B,C),subclass_of(A,B).
  194
  195
  196%! extract_subontology(+ClassName, +File) is det.
  197%
  198%  given a query ClassName, extract a sub-ontology based around that class using subont/3
  199%  and save turtle to File
  200extract_subontology(CN,File) :-
  201        ensure_loaded(library(semweb/turtle)),
  202        forall('??'(wd,(label(C,CN@en),subont(C,A,B),enlabel(A,AN))),               (   rdf_assert(A,rdfs:subClassOf,B,File),                   rdf_assert(A,rdf:type,owl:'Class',File),                   rdf_assert(A,rdfs:label,AN,File))),        rdf_save_turtle(File,[graph(File)]).
 enlabel(?Entity, ?Name) is nondet
Name is the English language name of Entity
  211enlabel(E,N) :- label(E,N),lang(N)="en".
 enlabelp(?Entity, ?Name) is nondet
Name is the English language name of X where X is a directClaim on Entity
  216enlabelp(E,N) :- rdf(X,wbont:directClaim,E),enlabel(X,N).
 enlabel_any(?Entity, ?Name) is nondet
either enlabel/2 or enlabelp/2
  221enlabel_any(E,N) :- enlabel(E,N).
  222enlabel_any(E,N) :- enlabelp(E,N).
 en_alt_label(?Entity, ?Name) is nondet
as enlabel/2 but using skos altLabel
  227en_alt_label(E,N) :- rdf(E,skos:altLabel,N),lang(N)="en".
 en_description(?Entity, ?Desc) is nondet
Desc is a description of Entity
  233en_description(E,N) :- rdf(E,'http://schema.org/description',N),lang(N)="en".
 entity_search(+SearchTerm, ?Item) is nondet
 entity_search(+SearchTerm, ?Item, +Limit:int) is nondet
named entity search, using the wikibase EntitySearch function
  241entity_search(Term, Item) :-
  242        entity_search(Term, Item, 1).
  243
  244entity_search(Term, Item, Limit) :-
  245        service(wikibase:mwapi,
  246                (   rdf(bd:serviceParam, wikibase:api, "EntitySearch"^^xsd:string),
  247                    rdf(bd:serviceParam, wikibase:endpoint, "www.wikidata.org"^^xsd:string),
  248                    rdf(bd:serviceParam, mwapi:search, Term@en),
  249                    rdf(bd:serviceParam, mwapi:language, "en"^^xsd:string),
  250                    rdf(bd:serviceParam, mwapi:limit, Limit ^^ xsd:int),
  251                    rdf(Item, wikibase:apiOutputItem, mwapi:item))).
  252
  253        
  254
  255
  256% --------------------
  257% classes
  258% --------------------
  259
  260% geography
  261
  262
  263% --------------------
  264% predicates
  265% --------------------
  266
  267% PROPS
  268
  269% meta
  270pname_wid(meta,instance_of, p31).
  271pname_wid(meta,subclass_of, p279).
  272pname_wid(meta,subproperty_of, p1647).
  273pname_wid(meta,equivalent_property, p1628).
  274pname_wid(meta,property_constraint, p2302).
  275pname_wid(meta,properties_for_this_type, p1963).
  276
  277pname_wid(meta,point_in_time, p585).
  278
  279
  280instance_of_name(I,CN) :-
  281        instance_of(I,C),
  282        rdf(C,rdfs:label,CN@en).
  283entailed_instance_of_name(I,CN) :-
  284        instance_of(I,C1),
  285        subclass_of_transitive(C1,C),
  286        rdf(C,rdfs:label,CN@en).
  287
  288
  289property_constraint_pv(P,C,PP,V) :-
  290        property_constraint_e2s(P,S),
  291        rdf(S,PP,V),
  292        property_constraint_s2v(S,C).
  293
  294% general
  295pname_wid(meta,author, p50).
  296pname_wid(meta,exact_match, p2888).
  297
  298pname_wid(general,part_of, p361).
  299
  300
  301% bio
  302
  303% IDs
  304pname_wid(bio,hp_id, p3841).
  305pname_wid(bio,envo_id, p3859).
  306pname_wid(bio,doid_id, p699).
  307pname_wid(bio,chebi_id, p683).
  308pname_wid(bio,uniprot_id, p352).
  309pname_wid(bio,ncbigene_id, p351).
  310pname_wid(bio,ipr_id, p2926).
  311pname_wid(bio,civic_id, p3329).
  312pname_wid(bio,ro_id, p3590).
  313pname_wid(bio,mesh_id, p486).
  314pname_wid(bio,go_id, p686).
  315pname_wid(bio,ncbitaxon_id, p685).
  316pname_wid(bio,uberon_id, p1554).
  317pname_wid(bio,umls_id, p2892).
  318pname_wid(bio,drugbank_id, p715).
  319
  320% bio rels
  321pname_wid(bio,encodes, p688).
  322pname_wid(bio,genetic_association, p2293).
  323pname_wid(bio,treated_by_drug, p2176).
  324pname_wid(bio,symptoms, p780).
  325pname_wid(bio,pathogen_transmission_process, p1060).
  326pname_wid(bio,has_cause, p828).
  327pname_wid(bio,biological_variant_of, p3433).
  328pname_wid(bio,has_part, p527).
  329
  330% https://www.wikidata.org/wiki/Wikidata:SPARQL_query_service/queries/examples#Get_known_variants_reported_in_CIViC_database_(Q27612411)_of_genes_reported_in_a_Wikipathways_pathway:_Bladder_Cancer_(Q30230812)
  331pname_wid(bio,positive_therapeutic_predictor, p3354).
  332pname_wid(bio,negative_therapeutic_predictor, p3355).
  333pname_wid(bio,positive_diagnostic_predictor, p3356).
  334pname_wid(bio,negative_diagnostic_predictor, p3357).
  335pname_wid(bio,positive_prognostic_predictor, p3358).
  336pname_wid(bio,negative_prognostic_predictor, p3359).
  337pname_wid(bio,medical_condition_treated, p2175).
  338
  339% beacon
  340pname_wid(bio,physically_interacts_with, p129).
  341pname_wid(bio,location, p276).
  342pname_wid(bio,manifestation_of, p1557).
  343pname_wid(bio,followed_by, p156).
  344pname_wid(bio,product_or_material_produced, p1056).
  345pname_wid(bio,uses, p2283).
  346pname_wid(bio,has_effect, p1542).
  347pname_wid(bio,drug_used_for_treatment, p2176).
  348pname_wid(bio,found_in_taxon, p703).
  349pname_wid(bio,ortholog, p684).
  350pname_wid(bio,biological_process, p682).
  351pname_wid(bio,cell_component, p681).
  352pname_wid(bio,molecular_function, p680).
  353pname_wid(bio,has_quality, p1552).
  354pname_wid(bio,regulates, p128).
  355
  356% time
 in_time_interval(+Start, +End, +Time) is semidet
true if Time is an xsd:date between Start and End dates
  361in_time_interval(Start,End,Time) :-
  362        Time >= Start,
  363        Time =< End.
  364        
  365    
  366% CLASSES
  367
  368% env
  369cname_wid(geo,ecosystem, q37813).
  370
  371% geo
  372cname_wid(geo,geographic_entity, q27096213).
  373cname_wid(geo,continent, q5107).
  374cname_wid(geo,country, q6256).
  375cname_wid(geo,city, q515).
  376cname_wid(geo,river, q4022).
  377cname_wid(geo,landform, q271669).
  378cname_wid(geo,undersea_landform, q55182671).
  379cname_wid(geo,wetland,q170321).
  380cname_wid(geo,forest,q4421).
  381cname_wid(geo,protected_area,q3825807).
  382
  383
  384pname_wid(geo,population, p1082).
  385pname_wid(geo,part_of_continent, p30).
  386pname_wid(geo,coordinate_location, p625). 
  387pname_wid(geo,elevation_above_sea_level, p2044). 
  388pname_wid(geo,located_on_terrain_feature, p706).
  389pname_wid(geo,tributary,p974).
  390
  391
  392
  393pname_wid(geo,geonames_id, p1566).
  394pname_wid(geo,geonames_feature_code, p2452).
 population_at(?PopulatedPlace, ?Population, ?Time) is nondet
PopulatedPlace has a population size of Population at Time
  399population_at(E,Pop,Time) :-
  400        population_e2s(E,S),
  401        point_in_time_s2q(S,Time),
  402        population_s2v(S,Pop).
 coordinate_location_node(?Entity, ?Node) is nondet
in general you do not need to use this directly
  408coordinate_location_node(E,N) :-
  409        coordinate_location_e2s(E,S),
  410        coordinate_location_psv(S,N).
 geolocation(?Entity, ?Lat, ?Long, ?Precision, ?Globe) is nondet
Entity is located at Lat-Long on Globe
  415geolocation(E,Lat,Long,Precision,Globe) :-
  416        coordinate_location_node(E,N),
  417        node_geolocation(N,Lat,Long,Precision,Globe).
  418geolocation(E,Lat,Long,Precision) :-
  419        coordinate_location_node(E,N),
  420        node_geolocation(N,Lat,Long,Precision).
  421geolocation(E,Lat,Long) :-
  422        coordinate_location_node(E,N),
  423        node_geolocation(N,Lat,Long).
  424
  425node_geolocation(N,Lat,Long,Precision,Globe) :-
  426        rdf(N,wbont:geoLatitude,Lat),
  427        rdf(N,wbont:geoLongitude,Long),
  428        rdf(N,wbont:geoPrecision,Precision),
  429        rdf(N,wbont:geoGlobe,Globe).
  430node_geolocation(N,Lat,Long,Precision) :-
  431        rdf(N,wbont:geoLatitude,Lat),
  432        rdf(N,wbont:geoLongitude,Long),
  433        rdf(N,wbont:geoPrecision,Precision).
  434node_geolocation(N,Lat,Long) :-
  435        rdf(N,wbont:geoLatitude,Lat),
  436        rdf(N,wbont:geoLongitude,Long).
  437
  438%% geolocation_around(+Center, +Radius, ?Entity) is nondet.
  439%
  440%  true if Entity is found within Radium miles of Center.
  441%  use coordinate_location/2 to map between a GeoEntity and its Center
  442geolocation_around(Center, Radius, X) :-
  443        service(wikibase:around,
  444                (   coordinate_location(X,_Loc),
  445                    rdf(bd:serviceParam,wikibase:center,Center),
  446                    rdf(bd:serviceParam,wikibase:radius,Radius^^xsd:float))).
  447        
  448
  449% https://www.wikidata.org/wiki/Wikidata:SPARQL_query_service/queries#Working_with_coordinates
  450
  451% chem
  452cname_wid(chem,chemical_property, q21294996).
  453pname_wid(chem,median_lethal_dose, p2240).
  454
  455
  456% bio
  457cname_wid(bio,bioproperty, q22988603).
  458
  459cname_wid(bio,cancer, q12078).
  460cname_wid(bio,disease, q12136).
  461cname_wid(bio,infectious_disease, q18123741).
  462
  463cname_wid(bio,chemical_compound, q11173).
  464cname_wid(bio,chemical_element, q11344).
  465cname_wid(bio,drug, q12140).
  466
  467cname_wid(bio,symptom, q169872).
  468cname_wid(bio,medical_finding, q639907).
  469cname_wid(bio,trait, q1211967).
  470cname_wid(bio,pathway, q4915012).
  471cname_wid(bio,macromolecular_complex, q22325163).
  472cname_wid(bio,gene, q7187).
  473cname_wid(bio,gene_product, q424689).
  474cname_wid(bio,sequence_variant, q15304597).
  475
  476cname_wid(bio,hazard, q1132455).
  477
  478cname_wid(bio,therapy, q179661).
  479cname_wid(bio,medical_procedure, q796194).
  480
  481
  482% random
  483cname_wid(geo,power_station, q159719).
  484
  485% TODO
  486%nary(ptp_var_drug_condition, positive_therapeutic_predictor, medical_condition_treated).
  487
  488
  489
  490var_drug_condition(V,D,C,positive_therapeutic_predictor) :-
  491        positive_therapeutic_predictor_e2s(V,S),
  492        medical_condition_treated_s2q(S,C),
  493        positive_therapeutic_predictor_s2v(S,D)