1:- module(ubergraph,
    2          [
    3           rdf_ontology/3,
    4           rdf_closure/3,
    5           rdf_nr/3,
    6           rdf_redundant/3,
    7
    8           metatype/2,
    9
   10           anc/3,
   11
   12           simj/3,
   13           simj/4,
   14           simj_e/3,
   15           simj_e/4,
   16           ancestor_intersection/3,
   17           ancestor_intersection/4,
   18           ancestor_union/3,
   19           ancestor_union/4,
   20
   21           taxon/1,
   22           never_in_taxon/2,
   23           not_in_taxon_1/3,
   24           not_in_taxon_2/3,
   25           conservative_not_in_taxon/2,
   26           not_in_taxon/3,
   27           taxon_propagating_property/1
   28           ]).   29
   30:- use_module(library(sparqlprog)).   31:- use_module(library(semweb/rdf11)).   32
   33:- rdf_register_prefix(ubergraph,'http://reasoner.renci.org/').   34:- rdf_register_prefix(obo,'http://purl.obolibrary.org/obo/').   35:- rdf_register_prefix(biolink, 'https://w3id.org/biolink/vocab/').   36:- rdf_register_prefix('NCBITaxon', 'http://purl.obolibrary.org/obo/NCBITaxon_').   37:- rdf_register_prefix('UBERON', 'http://purl.obolibrary.org/obo/UBERON_').   38
   39    
   40rdf_ontology(S,P,O):- rdf(S,P,O,ubergraph:ontology).
   41rdf_closure(S,P,O):- rdf(S,P,O,ubergraph:'ontology/closure').
   42rdf_nr(S,P,O):- rdf(S,P,O,ubergraph:nonredundant).
   43rdf_redundant(S,P,O):- rdf(S,P,O,ubergraph:redundant).
 metatype(?Cls, ?MetaCls) is nondet
e.g. metatype(C,biolink:'Disease')
   48metatype(C,MC) :-
   49        rdf(MC,skos:exactMatch,M),
   50        subClassOf(C,M).
 anc(?Cls, +Rel, ?Parent) is nondet
reflexive ancestor over Rel note that ubergraph does not materialize reflexive
   56anc(C,R,P) :- rdf_path(C,R|rdfs:subClassOf,P).
   57
   58
   59ancestor_intersection(C1,C2,Num) :-
   60        aggregate(count(distinct(P)),(subClassOf(C1,P),subClassOf(C2,P)),Num).
   61ancestor_union(C1,C2,Num) :-
   62        aggregate(count(distinct(P)),(subClassOf(C1,P);subClassOf(C2,P)),Num).
   63
   64ancestor_intersection(C1,C2,R,Num) :-
   65        aggregate(count(distinct(P)),(anc(C1,R,P),anc(C2,R,P)),Num).
   66ancestor_union(C1,C2,R,Num) :-
   67        aggregate(count(distinct(P)),(anc(C1,R,P);anc(C2,R,P)),Num).
Jaccard similarity (entirely in SPARQL)
   74simj(C1,C2,S) :-
   75        ancestor_intersection(C1,C2,AI),
   76        ancestor_union(C1,C2,AU),
   77        S is AI/AU.
   78simj(C1,C2,R,S) :-
   79        ancestor_intersection(C1,C2,R,AI),
   80        ancestor_union(C1,C2,R,AU),
   81        S is AI/AU.
Jaccard similarity (mixed sparql/prolog)

If R is specified then ancestor is calculated over this relation as well as subclass

inner goals are evaluated using 2 sparql calls

   91simj_e(C1,C2,S) :-
   92        ??(ubergraph, ancestor_intersection(C1,C2,AI)),
   93        ??(ubergraph, ancestor_union(C1,C2,AU)),
   94        bind(AI/AU,S).
   95simj_e(C1,C2,R,S) :-
   96        ??(ubergraph, ancestor_intersection(C1,C2,R,AI)),
   97        ??(ubergraph, ancestor_union(C1,C2,R,AU)),
   98        bind(AI/AU,S).
  104% NCBITaxon:4930 ! Saccharomyces
  105% UBERON:0000955 ! brain
  106
  107taxon(T) :-     subClassOf(T,'NCBITaxon':'1').
  108
  109never_in_taxon(C,T) :- rdf(C,'http://purl.obolibrary.org/obo/RO_0002161',T).
  110
  111not_in_taxon_1(C,P,T) :-
  112        rdf(C,P,C1),
  113        in_taxon(C1,T1),
  114        \+ subClassOf(T,T1).
  115not_in_taxon_2(C,P,T) :-
  116        rdf(C,P,C1),
  117        never_in_taxon(C1,T1),
  118        subClassOf(T,T1).
  119
  120not_in_taxon(C,P,T) :- not_in_taxon_1(C,P,T).
  121not_in_taxon(C,P,T) :- not_in_taxon_2(C,P,T).
  122
  123conservative_not_in_taxon(C,T) :-
  124        not_in_taxon(C,P,T),
  125        taxon_propagating_property(P).
  126
  127taxon_propagating_property(rdfs:subClassOf).
  128taxon_propagating_property(obo:'BFO_0000066').
  129taxon_propagating_property(obo:'BFO_0000051').
  130taxon_propagating_property(obo:'BFO_0000050')