1:- module(ncit,
    2          [
    3           gene_associated_with_disease/2,
    4           gene_associated_with_disease_inf/3,
    5
    6           disease_has_finding_svf/2
    7           ]).    8
    9:- use_module(library(sparqlprog)).   10:- use_module(library(semweb/rdf11)).   11
   12:- sparql_endpoint( ncit, 'https://stars-app.renci.org/ncitgraph/sparql').   13
   14:- rdf_register_prefix('NCIT','http://purl.obolibrary.org/obo/NCIT_').   15
   16gene_associated_with_disease(G,D) :- rdf(G,'NCIT':'R38',D).
   17gene_associated_with_disease_inf(G,D,X) :- rdf(G,'NCIT':'R38',X),rdfs_subclass_of(X,D).
   18
   19disease_has_finding_svf(D,F) :- subclass_of_some(D,'NCIT':'R108',F)