1:- module(uniprot,
2 [
3 protein/1,
4 disease_annotation/1,
5 has_disease_annotation/2,
6 natural_variant_annotation/1,
7 has_natural_variant_annotation/2,
8 protein_natural_variant_disease/3,
9 protein_natural_variant_disease_xref/4,
10 protein_natural_variant_disease_dbsnp/4,
11 is_dbsnp/1,
12
13 transmembrane_annotation/1,
14 has_transmembrane_annotation/2,
15
16 mnemonic/2,
17 encoded_by/2,
18
19 annotation_range/4,
20 protein_annotation_range/5,
21 protein_begin/3,
22
23 in_taxon/2,
24 in_human/1,
25
26 reviewed/1,
27 annotation/2,
28 database/2,
29
30 substitution/2,
31
32 xref/2,
33 xref_interpro/2,
34 xref_panther/2,
35 xref_pro/2,
36 is_interpro/1,
37 is_panther/1,
38 is_pro/1,
39 has_full_name/2,
40
41 pref_label/2,
42 recommended_name/2
43 ]). 44
45:- use_module(library(sparqlprog/ontologies/faldo)). 46:- use_module(library(sparqlprog)). 47
48:- use_module(library(sparqlprog/owl_types)). 49:- use_module(library(typedef)). 50
51:- rdf_register_prefix(up,'http://purl.uniprot.org/core/'). 52:- rdf_register_prefix(updb,'http://purl.uniprot.org/database/'). 53:- rdf_register_prefix(uniprot,'http://purl.uniprot.org/uniprot/'). 54:- rdf_register_prefix(uptaxon,'http://purl.uniprot.org/taxonomy/'). 55:- rdf_register_prefix(skos, 'http://www.w3.org/2004/02/skos/core#'). 56:- rdf_register_prefix(embl_csd, 'http://purl.uniprot.org/embl-cds/'). 57
58:- sparql_endpoint( uniprot, 'http://sparql.uniprot.org/sparql'). 59
60
61:- type uniprot_protein ---> atomic_iri.
62:- type uniprot_annotation ---> atomic_iri.
63:- type uniprot_disease_annotation ---> uniprot_annotation.
64:- type uniprot_xref ---> atomic_iri.
65:- type uniprot_term ---> atomic_iri.
66:- type uniprot_sequence_string ---> string ^^ xsd_type.
72protein(C) :- rdf(C,rdf:type,up:'Protein').
79disease_annotation(A) :- rdf(A,rdf:type,up:'Disease_Annotation').
85has_disease_annotation(P,A) :- annotation(P,A),rdf(A,rdf:type,up:'Disease_Annotation').
92natural_variant_annotation(A) :- rdf(A,rdf:type,up:'Natural_Variant_Annotation').
98has_natural_variant_annotation(P,A) :- annotation(P,A),rdf(A,rdf:type,up:'Natural_Variant_Annotation').
105protein_natural_variant_disease(P,A,D) :- annotation(P,A),rdf(A,rdf:type,up:'Natural_Variant_Annotation'),rdf(A,skos:related,D).
112protein_natural_variant_disease_xref(P,A,D,X) :- annotation(P,A),rdf(A,rdf:type,up:'Natural_Variant_Annotation'),rdf(A,skos:related,D),rdf(A,rdfs:seeAlso,X).
118protein_natural_variant_disease_dbsnp(P,A,D,X) :- protein_natural_variant_disease_xref(P,A,D,X), is_dbsnp(X).
122is_dbsnp(X) :- rdf(X,up:database,updb:dbSNP).
127transmembrane_annotation(A) :- rdf(A,rdf:type,up:'Transmembrane_Annotation').
130has_transmembrane_annotation(P,A) :- annotation(P,A),rdf(A,rdf:type,up:'Transmembrane_Annotation').
135mnemonic(C,N) :- rdf(C,up:mnemonic,N).
138encoded_by(P,G) :- rdf(P,up:encodedBy,G).
142recommended_name(P,N) :- rdf(P,up:recommendedName,N).
145has_full_name(P,X) :- rdf(P,up:recommendedName,N), rdf(N,up:fullName,X).
146
150pref_label(E,N) :- rdf(E,skos:prefLabel,N).
154in_taxon(P,T) :- rdf(P,up:organism,T).
158annotation(P,A) :- rdf(P,up:annotation,A).
161database(X,D) :- rdf(X,up:database,D).
168protein_annotation_range(P,A,B,E,R) :-
169 protein_annotation(P,A),
170 annotation_range(P,B,E,R).
174annotation_range(P,B,E,R) :-
175 rdf(P,up:range,I),
176 begin_coord(I,B,R),
177 end_coord(I,E,R).
180protein_begin(P,B,R) :-
181 rdf(P,up:range,I),
182 begin_coord(I,B,R).
187classified_with(P,T) :- rdf(P,up:classifiedWith,T).
194substitution(A,S) :- rdf(A,up:substitution,S).
202xref(P,X) :- rdf(P,rdfs:seeAlso,X).
208xref_interpro(P,X) :- xref(P,X),is_interpro(X).
214xref_panther(P,X) :- xref(P,X),is_panther(X).
220xref_pro(P,X) :- xref(P,X),is_pro(X).
229is_interpro(X) :- database(X,updb:'InterPro').
235is_panther(X) :- database(X,updb:'PANTHER').
241is_pro(X) :- database(X,updb:'PRO').
250in_human(P) :- rdf(P,up:organism,uptaxon:'9606').
251
252
253%! reviewed(?P : uniprot_protein) is nondet.
254%
255% P is a protein with review status of true
256%
257reviewed(P) :- rdf(P,up:reviewed,true^^xsd:boolean).
258
259