1:- module(uniprot,
2 [
3 protein/1,
4 in_reference_proteome/1,
5 has_annotation_type/3,
6 disease_annotation/1,
7 has_disease_annotation/2,
8 natural_variant_annotation/1,
9 has_natural_variant_annotation/2,
10 protein_natural_variant_disease/3,
11 protein_natural_variant_disease_xref/4,
12 protein_natural_variant_disease_dbsnp/4,
13 is_dbsnp/1,
14
15 has_ptm_annotation/2,
16
17 modification_annotation/1,
18 peptide_annotation/1,
19 transmembrane_annotation/1,
20 has_transmembrane_annotation/2,
21
22 classified_with/2,
23 classified_with_go/2,
24 classified_with_go_mf/2,
25 classified_with_go_catalysis/2,
26 has_catalytic_activity/2,
27 protein_has_enzyme_class/2,
28 protein_has_catalyzed_reaction/2,
29 enzyme_class/2,
30 catalyzed_reaction/2,
31
32 mnemonic/2,
33 encoded_by/2,
34
35 annotation_range/4,
36 protein_annotation_range/5,
37 protein_begin/3,
38
39 in_taxon/2,
40 in_human/1,
41
42 reviewed/1,
43 annotation/2,
44 database/2,
45
46 substitution/2,
47
48 xref/2,
49 xref_intersection_count/3,
50 xref_union_count/3,
51 xref_in/3,
52 xref_interpro/2,
53 xref_panther/2,
54 xref_pro/2,
55 xref_araport/2,
56 xref_tair/2,
57 is_interpro/1,
58 is_panther/1,
59 is_pro/1,
60 is_organism_database/1,
61 is_organism_database/2,
62 is_xenbase/1,
63 is_wormbase/1,
64 has_full_name/2,
65
66 pref_label/2,
67 recommended_name/2,
68
69 rhea_count/2,
70
71 uniprot_class/1,
72 predicate_summary/5
73 ]). 74
75:- use_module(library(sparqlprog/ontologies/faldo)). 76:- use_module(library(sparqlprog)). 77
78:- use_module(library(sparqlprog/owl_types)). 79:- use_module(library(typedef)). 80
81:- rdf_register_prefix(up,'http://purl.uniprot.org/core/'). 82:- rdf_register_prefix(updb,'http://purl.uniprot.org/database/'). 83:- rdf_register_prefix(uniprot,'http://purl.uniprot.org/uniprot/'). 84:- rdf_register_prefix(uniprotkw,'http://purl.uniprot.org/keywords/'). 85:- rdf_register_prefix(uniprot_annotation,'http://purl.uniprot.org/annotation/'). 86:- rdf_register_prefix(uptaxon,'http://purl.uniprot.org/taxonomy/'). 87:- rdf_register_prefix(interpro,'http://purl.uniprot.org/interpro/'). 88:- rdf_register_prefix(skos, 'http://www.w3.org/2004/02/skos/core#'). 89:- rdf_register_prefix(embl_cds, 'http://purl.uniprot.org/embl-cds/'). 90:- rdf_register_prefix(rhea, 'http://rdf.rhea-db.org/'). 91:- rdf_register_prefix(enzyme, 'http://purl.uniprot.org/enzyme/'). 92:- rdf_register_prefix('GO', 'http://purl.obolibrary.org/obo/GO_'). 93
94:- sparql_endpoint( uniprot, 'http://sparql.uniprot.org/sparql'). 95
96:- type uniprot_protein ---> atomic_iri.
97:- type uniprot_annotation ---> atomic_iri.
98:- type uniprot_disease_annotation ---> uniprot_annotation.
99:- type uniprot_variant_annotation ---> uniprot_annotation.
100:- type uniprot_xref ---> atomic_iri.
101:- type uniprot_term ---> atomic_iri.
102:- type uniprot_sequence_string ---> string ^^ xsd_type.
103
104uniprot_class(C) :-
105 rdf(C,rdf:type,owl:'Class'),
106 str_starts(str(C),'http://purl.uniprot.org/core/').
107
108predicate_summary(P,ST,OT,Num,1) :-
109 ??(uniprot,
110 rdf(P,rdf:type,owl:'ObjectProperty')),
111 format('# ~w',[P]),
112 ??(uniprot,
113 uniprot_class(ST)),
114 ??(uniprot,
115 exists(rdf(_,rdf:type,ST))),
116 format('# ~w',[ST]),
117 ??(uniprot,
118 exists( (rdf(X,rdf:type,ST),rdf(X,P,_)))),
119 format('#f ~w',[P]),
120 ??(uniprot,
121 aggregate_group(count(O),
122 [OT],
123 ( rdf(S,rdf:type,ST),rdf(S,P,O),rdf(O,rdf:type,OT)),
124 Num)),
125 format('# ~w',[P/Num]).
134protein(C) :- rdf(C,rdf:type,up:'Protein').
135
136in_reference_proteome(C) :- rdf(C,up:classifiedWith,uniprotkw:'1185').
140has_annotation_type(P,A,T) :- annotation(P,A),rdf(A,rdf:type,T).
146disease_annotation(A) :- rdf(A,rdf:type,up:'Disease_Annotation').
152has_disease_annotation(P,A) :- annotation(P,A),rdf(A,rdf:type,up:'Disease_Annotation').
153
154
155has_ptm_annotation(P,A) :-
156 annotation(P,A),
157 rdf(A,rdf:type,up:'PTM_Annotation').
164natural_variant_annotation(A) :- rdf(A,rdf:type,up:'Natural_Variant_Annotation').
170has_natural_variant_annotation(P,A) :- annotation(P,A),rdf(A,rdf:type,up:'Natural_Variant_Annotation').
177protein_natural_variant_disease(P,A,D) :- annotation(P,A),rdf(A,rdf:type,up:'Natural_Variant_Annotation'),rdf(A,skos:related,D).
184protein_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).
190protein_natural_variant_disease_dbsnp(P,A,D,X) :- protein_natural_variant_disease_xref(P,A,D,X), is_dbsnp(X).
194modification_annotation(A) :- rdfs_individual_of(A,up:'Modification_Annotation').
198peptide_annotation(A) :- rdfs_individual_of(A,up:'Peptide_Annotation').
202transmembrane_annotation(A) :- rdf(A,rdf:type,up:'Transmembrane_Annotation').
205has_transmembrane_annotation(P,A) :- annotation(P,A),rdf(A,rdf:type,up:'Transmembrane_Annotation').
208has_catalytic_activity(P,CA) :- annotation(P,Ann),rdf(Ann,up:catalyticActivity,CA).
209
210
211catalyzed_reaction(CA,R) :- rdf(CA,up:catalyzedReaction,R).
212enzyme_class(CA,R) :- rdf(CA,up:enzymeClass,R).
213
215protein_has_catalyzed_reaction(P,R) :- has_catalytic_activity(P,A),catalyzed_reaction(A,R).
216protein_has_enzyme_class(P,R) :- has_catalytic_activity(P,A),enzyme_class(A,R).
221mnemonic(C,N) :- rdf(C,up:mnemonic,N).
224encoded_by(P,G) :- rdf(P,up:encodedBy,G).
228recommended_name(P,N) :- rdf(P,up:recommendedName,N).
231has_full_name(P,X) :- rdf(P,up:recommendedName,N), rdf(N,up:fullName,X).
232
236pref_label(E,N) :- rdf(E,skos:prefLabel,N).
240in_taxon(P,T) :- rdf(P,up:organism,T).
244annotation(P,A) :- rdf(P,up:annotation,A).
247database(X,D) :- rdf(X,up:database,D).
254protein_annotation_range(P,A,B,E,R) :-
255 annotation(P,A),
256 annotation_range(A,B,E,R).
260annotation_range(P,B,E,R) :-
261 rdf(P,up:range,I),
262 begin_coord(I,B,R),
263 end_coord(I,E,R).
266protein_begin(P,B,R) :-
267 rdf(P,up:range,I),
268 begin_coord(I,B,R).
273classified_with(P,T) :- rdf(P,up:classifiedWith,T).
274
275classified_with_go(P,T) :- rdf(P,up:classifiedWith,T),str_starts(str(T),"http://purl.obolibrary.org/obo/GO_").
276
278classified_with_go_mf(P,T) :- rdf(P,up:classifiedWith,T),rdf(T,zeroOrMore(rdfs:subClassOf),'GO':'0003674').
279
281classified_with_go_catalysis(P,T) :- rdf(P,up:classifiedWith,T),rdf(T,'http://purl.obolibrary.org/obo/IAO_0000115',Def),str_starts(Def,'Catalysis of the reaction:').
282
283
285alt_sequence_annotation(PF,A) :-
286 rdf(PF,up:modification,A),
287 rdf(A,rdf:type,up:'Alternative_Sequence_Annotation').
288isoform_region(PF,R) :-
289 alt_sequence_annotation(PF,A),
290 rdf(A,up:range,R).
300substitution(A,S) :- rdf(A,up:substitution,S).
308xref(P,X) :- rdf(P,rdfs:seeAlso,X).
309
310
311
312xref_in(P,X,DB) :- xref(P,X),database(X,updb:DB).
313
314
315xref_intersection_count(X1,X2,N) :-
316 aggregate(count(distinct(P)),(xref(P,X1),xref(P,X2)),N).
317xref_union_count(X1,X2,N) :-
318 aggregate(count(distinct(P)),(xref(P,X1);xref(P,X2)),N).
329in_human(P) :- rdf(P,up:organism,uptaxon:'9606').
330
331
332%! reviewed(?P : uniprot_protein) is nondet.
333%
334% P is a protein with review status of true
335%
336reviewed(P) :- rdf(P,up:reviewed,true^^xsd:boolean).
337
338
339rhea_count(R,Num) :-
340 aggregate(count(P),protein_has_catalyzed_reaction(P,R),Num).
341
342
349
350xref_organism_database(P,X) :-
351 xref(P,X),database(X,D), is_organism_database(D).
352is_organism_database(X) :-
353 is_organism_database(X,_).
354is_organism_database(X,D) :-
355 database(X,D),
356 member(D,
357 [
358 updb:'HGNC',
359 updb:'BioCyc',
360 updb:'MGI',
361 updb:'RGD',
362 updb:'SGD',
363 updb:'FlyBase',
364 updb:'PomBase',
365 updb:'dictyBase',
366 updb:'TAIR',
367 updb:'ZFIN',
368 updb:'WormBase',
369 updb:'Xenbase'
370 ]).
371
372
373
374
375is_ensembl(X) :- database(X,updb:'Ensembl').
376is_ensemblbacteria(X) :- database(X,updb:'EnsemblBacteria').
377is_ensemblfungi(X) :- database(X,updb:'EnsemblFungi').
378is_ensemblplants(X) :- database(X,updb:'EnsemblPlants').
379is_pdb(X) :- database(X,updb:'PDB').
380is_abcd(X) :- database(X,updb:'ABCD').
381is_allergome(X) :- database(X,updb:'Allergome').
382is_antibodypedia(X) :- database(X,updb:'Antibodypedia').
383is_arachnoserver(X) :- database(X,updb:'ArachnoServer').
384is_araport(X) :- database(X,updb:'Araport').
385is_bmrb(X) :- database(X,updb:'BMRB').
386is_brenda(X) :- database(X,updb:'BRENDA').
387is_bgee(X) :- database(X,updb:'Bgee').
388is_bindingdb(X) :- database(X,updb:'BindingDB').
389is_biocyc(X) :- database(X,updb:'BioCyc').
390is_biogrid(X) :- database(X,updb:'BioGRID').
391is_biogridorcs(X) :- database(X,updb:'BioGRID-ORCS').
392is_biomuta(X) :- database(X,updb:'BioMuta').
393is_cazy(X) :- database(X,updb:'CAZy').
394is_ccds(X) :- database(X,updb:'CCDS').
395is_cdd(X) :- database(X,updb:'CDD').
396is_cgd(X) :- database(X,updb:'CGD').
397is_clae(X) :- database(X,updb:'CLAE').
398is_compluyeast2dpage(X) :- database(X,updb:'COMPLUYEAST-2DPAGE').
399is_corum(X) :- database(X,updb:'CORUM').
400is_cptac(X) :- database(X,updb:'CPTAC').
401is_cptc(X) :- database(X,updb:'CPTC').
402is_ctd(X) :- database(X,updb:'CTD').
403is_carbonyldb(X) :- database(X,updb:'CarbonylDB').
404is_chembl(X) :- database(X,updb:'ChEMBL').
405is_chitars(X) :- database(X,updb:'ChiTaRS').
406is_collectf(X) :- database(X,updb:'CollecTF').
407is_complexportal(X) :- database(X,updb:'ComplexPortal').
408is_conoserver(X) :- database(X,updb:'ConoServer').
409is_depod(X) :- database(X,updb:'DEPOD').
410is_dip(X) :- database(X,updb:'DIP').
411is_dmdm(X) :- database(X,updb:'DMDM').
412is_dnasu(X) :- database(X,updb:'DNASU').
413is_dosaccobs2dpage(X) :- database(X,updb:'DOSAC-COBS-2DPAGE').
414is_disgenet(X) :- database(X,updb:'DisGeNET').
415is_disprot(X) :- database(X,updb:'DisProt').
416is_drugbank(X) :- database(X,updb:'DrugBank').
417is_drugcentral(X) :- database(X,updb:'DrugCentral').
418is_elm(X) :- database(X,updb:'ELM').
419is_embl(X) :- database(X,updb:'EMBL').
420is_epd(X) :- database(X,updb:'EPD').
421is_esther(X) :- database(X,updb:'ESTHER').
422is_echobase(X) :- database(X,updb:'EchoBASE').
423is_ensemblmetazoa(X) :- database(X,updb:'EnsemblMetazoa').
424is_ensemblprotists(X) :- database(X,updb:'EnsemblProtists').
425is_evolutionarytrace(X) :- database(X,updb:'EvolutionaryTrace').
426is_expressionatlas(X) :- database(X,updb:'ExpressionAtlas').
427is_flybase(X) :- database(X,updb:'FlyBase').
428is_gene3d(X) :- database(X,updb:'Gene3D').
429is_genecards(X) :- database(X,updb:'GeneCards').
430is_genedb(X) :- database(X,updb:'GeneDB').
431is_geneid(X) :- database(X,updb:'GeneID').
432is_genereviews(X) :- database(X,updb:'GeneReviews').
433is_genetree(X) :- database(X,updb:'GeneTree').
434is_genewiki(X) :- database(X,updb:'GeneWiki').
435is_genevisible(X) :- database(X,updb:'Genevisible').
436is_genomernai(X) :- database(X,updb:'GenomeRNAi').
437is_glyconnect(X) :- database(X,updb:'GlyConnect').
438is_glygen(X) :- database(X,updb:'GlyGen').
439is_gramene(X) :- database(X,updb:'Gramene').
440is_guidetopharmacology(X) :- database(X,updb:'GuidetoPHARMACOLOGY').
441is_hamap(X) :- database(X,updb:'HAMAP').
442is_hgnc(X) :- database(X,updb:'HGNC').
443is_hogenom(X) :- database(X,updb:'HOGENOM').
444is_hpa(X) :- database(X,updb:'HPA').
445is_ideal(X) :- database(X,updb:'IDEAL').
446is_imgt_genedb(X) :- database(X,updb:'IMGT_GENE-DB').
447is_inparanoid(X) :- database(X,updb:'InParanoid').
448is_intact(X) :- database(X,updb:'IntAct').
449is_interpro(X) :- database(X,updb:'InterPro').
450is_kegg(X) :- database(X,updb:'KEGG').
451is_legiolist(X) :- database(X,updb:'LegioList').
452is_leproma(X) :- database(X,updb:'Leproma').
453is_merops(X) :- database(X,updb:'MEROPS').
454is_mgi(X) :- database(X,updb:'MGI').
455is_mim(X) :- database(X,updb:'MIM').
456is_mint(X) :- database(X,updb:'MINT').
457is_maizegdb(X) :- database(X,updb:'MaizeGDB').
458is_malacards(X) :- database(X,updb:'MalaCards').
459is_massive(X) :- database(X,updb:'MassIVE').
460is_maxqb(X) :- database(X,updb:'MaxQB').
461is_metosite(X) :- database(X,updb:'MetOSite').
462is_moondb(X) :- database(X,updb:'MoonDB').
463is_moonprot(X) :- database(X,updb:'MoonProt').
464is_niagads(X) :- database(X,updb:'NIAGADS').
465is_ogp(X) :- database(X,updb:'OGP').
466is_oma(X) :- database(X,updb:'OMA').
467is_opentargets(X) :- database(X,updb:'OpenTargets').
468is_orphanet(X) :- database(X,updb:'Orphanet').
469is_orthodb(X) :- database(X,updb:'OrthoDB').
470is_panther(X) :- database(X,updb:'PANTHER').
471is_patric(X) :- database(X,updb:'PATRIC').
472is_pcddb(X) :- database(X,updb:'PCDDB').
473is_pdbsum(X) :- database(X,updb:'PDBsum').
474is_phibase(X) :- database(X,updb:'PHI-base').
475is_pir(X) :- database(X,updb:'PIR').
476is_pirsf(X) :- database(X,updb:'PIRSF').
477is_pride(X) :- database(X,updb:'PRIDE').
478is_prints(X) :- database(X,updb:'PRINTS').
479is_pro(X) :- database(X,updb:'PRO').
480is_prosite(X) :- database(X,updb:'PROSITE').
481is_pathwaycommons(X) :- database(X,updb:'PathwayCommons').
482is_paxdb(X) :- database(X,updb:'PaxDb').
483is_peptideatlas(X) :- database(X,updb:'PeptideAtlas').
484is_peroxibase(X) :- database(X,updb:'PeroxiBase').
485is_pfam(X) :- database(X,updb:'Pfam').
486is_pharmgkb(X) :- database(X,updb:'PharmGKB').
487is_pharos(X) :- database(X,updb:'Pharos').
488is_phosphositeplus(X) :- database(X,updb:'PhosphoSitePlus').
489is_phylomedb(X) :- database(X,updb:'PhylomeDB').
490is_plantreactome(X) :- database(X,updb:'PlantReactome').
491is_pombase(X) :- database(X,updb:'PomBase').
492is_promex(X) :- database(X,updb:'ProMEX').
493is_proteomicsdb(X) :- database(X,updb:'ProteomicsDB').
494is_pseudocap(X) :- database(X,updb:'PseudoCAP').
495is_rebase(X) :- database(X,updb:'REBASE').
496is_reproduction2dpage(X) :- database(X,updb:'REPRODUCTION-2DPAGE').
497is_rgd(X) :- database(X,updb:'RGD').
498is_rnact(X) :- database(X,updb:'RNAct').
499is_reactome(X) :- database(X,updb:'Reactome').
500is_refseq(X) :- database(X,updb:'RefSeq').
501is_sabiork(X) :- database(X,updb:'SABIO-RK').
502is_sasbdb(X) :- database(X,updb:'SASBDB').
503is_sfld(X) :- database(X,updb:'SFLD').
504is_sgd(X) :- database(X,updb:'SGD').
505is_signor(X) :- database(X,updb:'SIGNOR').
506is_smart(X) :- database(X,updb:'SMART').
507is_smr(X) :- database(X,updb:'SMR').
508is_string(X) :- database(X,updb:'STRING').
509is_supfam(X) :- database(X,updb:'SUPFAM').
510is_swiss2dpage(X) :- database(X,updb:'SWISS-2DPAGE').
511is_signalink(X) :- database(X,updb:'SignaLink').
512is_swisslipids(X) :- database(X,updb:'SwissLipids').
513is_swisspalm(X) :- database(X,updb:'SwissPalm').
514is_tair(X) :- database(X,updb:'TAIR').
515is_tcdb(X) :- database(X,updb:'TCDB').
516is_tigrfams(X) :- database(X,updb:'TIGRFAMs').
517is_topdownproteomics(X) :- database(X,updb:'TopDownProteomics').
518is_treefam(X) :- database(X,updb:'TreeFam').
519is_tuberculist(X) :- database(X,updb:'TubercuList').
520is_ucd2dpage(X) :- database(X,updb:'UCD-2DPAGE').
521is_ucsc(X) :- database(X,updb:'UCSC').
522is_unilectin(X) :- database(X,updb:'UniLectin').
523is_veupathdb(X) :- database(X,updb:'VEuPathDB').
524is_vgnc(X) :- database(X,updb:'VGNC').
525is_wbparasite(X) :- database(X,updb:'WBParaSite').
526is_world2dpage(X) :- database(X,updb:'World-2DPAGE').
527is_wormbase(X) :- database(X,updb:'WormBase').
528is_xenbase(X) :- database(X,updb:'Xenbase').
529is_zfin(X) :- database(X,updb:'ZFIN').
530is_dbsnp(X) :- database(X,updb:'dbSNP').
531is_dictybase(X) :- database(X,updb:'dictyBase').
532is_eggnog(X) :- database(X,updb:'eggNOG').
533is_euhcvdb(X) :- database(X,updb:'euHCVdb').
534is_iptmnet(X) :- database(X,updb:'iPTMnet').
535is_jpost(X) :- database(X,updb:'jPOST').
536is_nextprot(X) :- database(X,updb:'neXtProt').
537is_po(X) :- database(X,updb:'PO').
538is_mesh(X) :- database(X,updb:'MeSH').
539is_medgen(X) :- database(X,updb:'MedGen').
540is_go(X) :- database(X,updb:'go').
541
543
544xref_ensembl(P,X) :- xref(P,X),database(X,updb:'Ensembl').
545xref_ensemblbacteria(P,X) :- xref(P,X),database(X,updb:'EnsemblBacteria').
546xref_ensemblfungi(P,X) :- xref(P,X),database(X,updb:'EnsemblFungi').
547xref_ensemblplants(P,X) :- xref(P,X),database(X,updb:'EnsemblPlants').
548xref_pdb(P,X) :- xref(P,X),database(X,updb:'PDB').
549xref_abcd(P,X) :- xref(P,X),database(X,updb:'ABCD').
550xref_allergome(P,X) :- xref(P,X),database(X,updb:'Allergome').
551xref_antibodypedia(P,X) :- xref(P,X),database(X,updb:'Antibodypedia').
552xref_arachnoserver(P,X) :- xref(P,X),database(X,updb:'ArachnoServer').
553xref_araport(P,X) :- xref(P,X),database(X,updb:'Araport').
554xref_bmrb(P,X) :- xref(P,X),database(X,updb:'BMRB').
555xref_brenda(P,X) :- xref(P,X),database(X,updb:'BRENDA').
556xref_bgee(P,X) :- xref(P,X),database(X,updb:'Bgee').
557xref_bindingdb(P,X) :- xref(P,X),database(X,updb:'BindingDB').
558xref_biocyc(P,X) :- xref(P,X),database(X,updb:'BioCyc').
559xref_biogrid(P,X) :- xref(P,X),database(X,updb:'BioGRID').
560xref_biogridorcs(P,X) :- xref(P,X),database(X,updb:'BioGRID-ORCS').
561xref_biomuta(P,X) :- xref(P,X),database(X,updb:'BioMuta').
562xref_cazy(P,X) :- xref(P,X),database(X,updb:'CAZy').
563xref_ccds(P,X) :- xref(P,X),database(X,updb:'CCDS').
564xref_cdd(P,X) :- xref(P,X),database(X,updb:'CDD').
565xref_cgd(P,X) :- xref(P,X),database(X,updb:'CGD').
566xref_clae(P,X) :- xref(P,X),database(X,updb:'CLAE').
567xref_compluyeast2dpage(P,X) :- xref(P,X),database(X,updb:'COMPLUYEAST-2DPAGE').
568xref_corum(P,X) :- xref(P,X),database(X,updb:'CORUM').
569xref_cptac(P,X) :- xref(P,X),database(X,updb:'CPTAC').
570xref_cptc(P,X) :- xref(P,X),database(X,updb:'CPTC').
571xref_ctd(P,X) :- xref(P,X),database(X,updb:'CTD').
572xref_carbonyldb(P,X) :- xref(P,X),database(X,updb:'CarbonylDB').
573xref_chembl(P,X) :- xref(P,X),database(X,updb:'ChEMBL').
574xref_chitars(P,X) :- xref(P,X),database(X,updb:'ChiTaRS').
575xref_collectf(P,X) :- xref(P,X),database(X,updb:'CollecTF').
576xref_complexportal(P,X) :- xref(P,X),database(X,updb:'ComplexPortal').
577xref_conoserver(P,X) :- xref(P,X),database(X,updb:'ConoServer').
578xref_depod(P,X) :- xref(P,X),database(X,updb:'DEPOD').
579xref_dip(P,X) :- xref(P,X),database(X,updb:'DIP').
580xref_dmdm(P,X) :- xref(P,X),database(X,updb:'DMDM').
581xref_dnasu(P,X) :- xref(P,X),database(X,updb:'DNASU').
582xref_dosaccobs2dpage(P,X) :- xref(P,X),database(X,updb:'DOSAC-COBS-2DPAGE').
583xref_disgenet(P,X) :- xref(P,X),database(X,updb:'DisGeNET').
584xref_disprot(P,X) :- xref(P,X),database(X,updb:'DisProt').
585xref_drugbank(P,X) :- xref(P,X),database(X,updb:'DrugBank').
586xref_drugcentral(P,X) :- xref(P,X),database(X,updb:'DrugCentral').
587xref_elm(P,X) :- xref(P,X),database(X,updb:'ELM').
588xref_embl(P,X) :- xref(P,X),database(X,updb:'EMBL').
589xref_epd(P,X) :- xref(P,X),database(X,updb:'EPD').
590xref_esther(P,X) :- xref(P,X),database(X,updb:'ESTHER').
591xref_echobase(P,X) :- xref(P,X),database(X,updb:'EchoBASE').
592xref_ensemblmetazoa(P,X) :- xref(P,X),database(X,updb:'EnsemblMetazoa').
593xref_ensemblprotists(P,X) :- xref(P,X),database(X,updb:'EnsemblProtists').
594xref_evolutionarytrace(P,X) :- xref(P,X),database(X,updb:'EvolutionaryTrace').
595xref_expressionatlas(P,X) :- xref(P,X),database(X,updb:'ExpressionAtlas').
596xref_flybase(P,X) :- xref(P,X),database(X,updb:'FlyBase').
597xref_gene3d(P,X) :- xref(P,X),database(X,updb:'Gene3D').
598xref_genecards(P,X) :- xref(P,X),database(X,updb:'GeneCards').
599xref_genedb(P,X) :- xref(P,X),database(X,updb:'GeneDB').
600xref_geneid(P,X) :- xref(P,X),database(X,updb:'GeneID').
601xref_genereviews(P,X) :- xref(P,X),database(X,updb:'GeneReviews').
602xref_genetree(P,X) :- xref(P,X),database(X,updb:'GeneTree').
603xref_genewiki(P,X) :- xref(P,X),database(X,updb:'GeneWiki').
604xref_genevisible(P,X) :- xref(P,X),database(X,updb:'Genevisible').
605xref_genomernai(P,X) :- xref(P,X),database(X,updb:'GenomeRNAi').
606xref_glyconnect(P,X) :- xref(P,X),database(X,updb:'GlyConnect').
607xref_glygen(P,X) :- xref(P,X),database(X,updb:'GlyGen').
608xref_gramene(P,X) :- xref(P,X),database(X,updb:'Gramene').
609xref_guidetopharmacology(P,X) :- xref(P,X),database(X,updb:'GuidetoPHARMACOLOGY').
610xref_hamap(P,X) :- xref(P,X),database(X,updb:'HAMAP').
611xref_hgnc(P,X) :- xref(P,X),database(X,updb:'HGNC').
612xref_hogenom(P,X) :- xref(P,X),database(X,updb:'HOGENOM').
613xref_hpa(P,X) :- xref(P,X),database(X,updb:'HPA').
614xref_ideal(P,X) :- xref(P,X),database(X,updb:'IDEAL').
615xref_imgt_genedb(P,X) :- xref(P,X),database(X,updb:'IMGT_GENE-DB').
616xref_inparanoid(P,X) :- xref(P,X),database(X,updb:'InParanoid').
617xref_intact(P,X) :- xref(P,X),database(X,updb:'IntAct').
618xref_interpro(P,X) :- xref(P,X),database(X,updb:'InterPro').
619xref_kegg(P,X) :- xref(P,X),database(X,updb:'KEGG').
620xref_legiolist(P,X) :- xref(P,X),database(X,updb:'LegioList').
621xref_leproma(P,X) :- xref(P,X),database(X,updb:'Leproma').
622xref_merops(P,X) :- xref(P,X),database(X,updb:'MEROPS').
623xref_mgi(P,X) :- xref(P,X),database(X,updb:'MGI').
624xref_mim(P,X) :- xref(P,X),database(X,updb:'MIM').
625xref_mint(P,X) :- xref(P,X),database(X,updb:'MINT').
626xref_maizegdb(P,X) :- xref(P,X),database(X,updb:'MaizeGDB').
627xref_malacards(P,X) :- xref(P,X),database(X,updb:'MalaCards').
628xref_massive(P,X) :- xref(P,X),database(X,updb:'MassIVE').
629xref_maxqb(P,X) :- xref(P,X),database(X,updb:'MaxQB').
630xref_metosite(P,X) :- xref(P,X),database(X,updb:'MetOSite').
631xref_moondb(P,X) :- xref(P,X),database(X,updb:'MoonDB').
632xref_moonprot(P,X) :- xref(P,X),database(X,updb:'MoonProt').
633xref_niagads(P,X) :- xref(P,X),database(X,updb:'NIAGADS').
634xref_ogp(P,X) :- xref(P,X),database(X,updb:'OGP').
635xref_oma(P,X) :- xref(P,X),database(X,updb:'OMA').
636xref_opentargets(P,X) :- xref(P,X),database(X,updb:'OpenTargets').
637xref_orphanet(P,X) :- xref(P,X),database(X,updb:'Orphanet').
638xref_orthodb(P,X) :- xref(P,X),database(X,updb:'OrthoDB').
639xref_panther(P,X) :- xref(P,X),database(X,updb:'PANTHER').
640xref_patric(P,X) :- xref(P,X),database(X,updb:'PATRIC').
641xref_pcddb(P,X) :- xref(P,X),database(X,updb:'PCDDB').
642xref_pdbsum(P,X) :- xref(P,X),database(X,updb:'PDBsum').
643xref_phibase(P,X) :- xref(P,X),database(X,updb:'PHI-base').
644xref_pir(P,X) :- xref(P,X),database(X,updb:'PIR').
645xref_pirsf(P,X) :- xref(P,X),database(X,updb:'PIRSF').
646xref_pride(P,X) :- xref(P,X),database(X,updb:'PRIDE').
647xref_prints(P,X) :- xref(P,X),database(X,updb:'PRINTS').
648xref_pro(P,X) :- xref(P,X),database(X,updb:'PRO').
649xref_prosite(P,X) :- xref(P,X),database(X,updb:'PROSITE').
650xref_pathwaycommons(P,X) :- xref(P,X),database(X,updb:'PathwayCommons').
651xref_paxdb(P,X) :- xref(P,X),database(X,updb:'PaxDb').
652xref_peptideatlas(P,X) :- xref(P,X),database(X,updb:'PeptideAtlas').
653xref_peroxibase(P,X) :- xref(P,X),database(X,updb:'PeroxiBase').
654xref_pfam(P,X) :- xref(P,X),database(X,updb:'Pfam').
655xref_pharmgkb(P,X) :- xref(P,X),database(X,updb:'PharmGKB').
656xref_pharos(P,X) :- xref(P,X),database(X,updb:'Pharos').
657xref_phosphositeplus(P,X) :- xref(P,X),database(X,updb:'PhosphoSitePlus').
658xref_phylomedb(P,X) :- xref(P,X),database(X,updb:'PhylomeDB').
659xref_plantreactome(P,X) :- xref(P,X),database(X,updb:'PlantReactome').
660xref_pombase(P,X) :- xref(P,X),database(X,updb:'PomBase').
661xref_promex(P,X) :- xref(P,X),database(X,updb:'ProMEX').
662xref_proteomicsdb(P,X) :- xref(P,X),database(X,updb:'ProteomicsDB').
663xref_pseudocap(P,X) :- xref(P,X),database(X,updb:'PseudoCAP').
664xref_rebase(P,X) :- xref(P,X),database(X,updb:'REBASE').
665xref_reproduction2dpage(P,X) :- xref(P,X),database(X,updb:'REPRODUCTION-2DPAGE').
666xref_rgd(P,X) :- xref(P,X),database(X,updb:'RGD').
667xref_rnact(P,X) :- xref(P,X),database(X,updb:'RNAct').
668xref_reactome(P,X) :- xref(P,X),database(X,updb:'Reactome').
669xref_refseq(P,X) :- xref(P,X),database(X,updb:'RefSeq').
670xref_sabiork(P,X) :- xref(P,X),database(X,updb:'SABIO-RK').
671xref_sasbdb(P,X) :- xref(P,X),database(X,updb:'SASBDB').
672xref_sfld(P,X) :- xref(P,X),database(X,updb:'SFLD').
673xref_sgd(P,X) :- xref(P,X),database(X,updb:'SGD').
674xref_signor(P,X) :- xref(P,X),database(X,updb:'SIGNOR').
675xref_smart(P,X) :- xref(P,X),database(X,updb:'SMART').
676xref_smr(P,X) :- xref(P,X),database(X,updb:'SMR').
677xref_string(P,X) :- xref(P,X),database(X,updb:'STRING').
678xref_supfam(P,X) :- xref(P,X),database(X,updb:'SUPFAM').
679xref_swiss2dpage(P,X) :- xref(P,X),database(X,updb:'SWISS-2DPAGE').
680xref_signalink(P,X) :- xref(P,X),database(X,updb:'SignaLink').
681xref_swisslipids(P,X) :- xref(P,X),database(X,updb:'SwissLipids').
682xref_swisspalm(P,X) :- xref(P,X),database(X,updb:'SwissPalm').
683xref_tair(P,X) :- xref(P,X),database(X,updb:'TAIR').
684xref_tcdb(P,X) :- xref(P,X),database(X,updb:'TCDB').
685xref_tigrfams(P,X) :- xref(P,X),database(X,updb:'TIGRFAMs').
686xref_topdownproteomics(P,X) :- xref(P,X),database(X,updb:'TopDownProteomics').
687xref_treefam(P,X) :- xref(P,X),database(X,updb:'TreeFam').
688xref_tuberculist(P,X) :- xref(P,X),database(X,updb:'TubercuList').
689xref_ucd2dpage(P,X) :- xref(P,X),database(X,updb:'UCD-2DPAGE').
690xref_ucsc(P,X) :- xref(P,X),database(X,updb:'UCSC').
691xref_unilectin(P,X) :- xref(P,X),database(X,updb:'UniLectin').
692xref_veupathdb(P,X) :- xref(P,X),database(X,updb:'VEuPathDB').
693xref_vgnc(P,X) :- xref(P,X),database(X,updb:'VGNC').
694xref_wbparasite(P,X) :- xref(P,X),database(X,updb:'WBParaSite').
695xref_world2dpage(P,X) :- xref(P,X),database(X,updb:'World-2DPAGE').
696xref_wormbase(P,X) :- xref(P,X),database(X,updb:'WormBase').
697xref_xenbase(P,X) :- xref(P,X),database(X,updb:'Xenbase').
698xref_zfin(P,X) :- xref(P,X),database(X,updb:'ZFIN').
699xref_dbsnp(P,X) :- xref(P,X),database(X,updb:'dbSNP').
700xref_dictybase(P,X) :- xref(P,X),database(X,updb:'dictyBase').
701xref_eggnog(P,X) :- xref(P,X),database(X,updb:'eggNOG').
702xref_euhcvdb(P,X) :- xref(P,X),database(X,updb:'euHCVdb').
703xref_iptmnet(P,X) :- xref(P,X),database(X,updb:'iPTMnet').
704xref_jpost(P,X) :- xref(P,X),database(X,updb:'jPOST').
705xref_nextprot(P,X) :- xref(P,X),database(X,updb:'neXtProt').
706xref_po(P,X) :- xref(P,X),database(X,updb:'PO').
707xref_mesh(P,X) :- xref(P,X),database(X,updb:'MeSH').
708xref_medgen(P,X) :- xref(P,X),database(X,updb:'MedGen').
709xref_go(P,X) :- xref(P,X),database(X,updb:'go')