wrapper that provides an obo-format like view over an OWL ontology

More details on obo format:

http://owlcollab.github.io/oboformat/doc/obo-syntax.html

In particular, this module provides:

*/

   16:- module(obo,
   17          [
   18           is_a/2,
   19           relationship/3,
   20           is_dangling/1,
   21           synprop_scope/2,
   22           entity_synonym_scope/2,
   23           entity_synonym_scope/3,
   24           entity_synonym_scope_type/4,
   25           entity_synonym_scope_xref/4,
   26           entity_xref_src/3,
   27           entity_xref_src/4,
   28           entity_xref_prefix/3
   29           ]).   30
   31:- use_module(library(obo_metadata/oio)).   32
   33:- use_module(library(semweb/rdf11)).   34:- use_module(library(semweb/rdfs)).   35:- use_module(library(sparqlprog/owl_util)).   36
   37:- reexport(library(obo_metadata/oio), [has_dbxref/2]).   38
   39:- rdf_register_ns(oio,'http://www.geneontology.org/formats/oboInOwl#').   40:- rdf_register_ns(def,'http://purl.obolibrary.org/obo/IAO_0000115').   41
   42synprop_scope('http://www.geneontology.org/formats/oboInOwl#hasRelatedSynonym','RELATED').
   43synprop_scope('http://www.geneontology.org/formats/oboInOwl#hasNarrowSynonym','NARROW').
   44synprop_scope('http://www.geneontology.org/formats/oboInOwl#hasBroadSynonym','BROAD').
   45synprop_scope('http://www.geneontology.org/formats/oboInOwl#hasExactSynonym','EXACT').
 is_a(?A, ?B) is nondet
subClassOf between two names classes
   52is_a(A,B) :-
   53        rdf(A,rdfs:subClassOf,B),
   54        rdf_is_iri(B),
   55        rdf_is_iri(A).
   56is_a(A,B) :-
   57        rdf(A,rdfs:subPropertyOf,B),
   58        rdf_is_iri(B),
   59        rdf_is_iri(A).
 relationship(?E, ?R, ?O) is nondet
true if E subClassOf R some O
   65relationship(E,R,O) :-
   66        rdf(E,rdfs:subClassOf,Res),
   67        owl_some(Res,R,O),
   68        \+ rdf_is_bnode(O).
 is_dangling(?E) is semidet
true if E has no label
   75is_dangling(E) :-
   76        \+ label(E,_).
 entity_synonym_scope(?E, ?V) is nondet
 entity_synonym_scope(?E, ?V, ?Scope) is nondet
true if V is a synonym for entity E, with a Scope of either: exact, broad, narrow, related
   85entity_synonym_scope(E,V,Scope) :-
   86        synprop_scope(P,Scope),
   87        rdf(E,P,V).
   88entity_synonym_scope(E,V) :-
   89        entity_synonym_scope(E,V,_).
 entity_synonym_scope_type(?E, ?V, ?Scope, ?Type) is nondet
As entity_synonym_scope/3 but also include the synonym type
   96entity_synonym_scope_type(E,V,Scope,Type) :-
   97        synprop_scope(P,Scope),
   98        triple_axiom_annotation(E,P,V,oio:hasSynonymType,Type).
 entity_synonym_scope_xref(?E, ?V, ?Scope, ?Xref) is nondet
As entity_synonym_scope/3 but also include the xref provenance for the synonym
  105entity_synonym_scope_xref(E,V,Scope,Xref) :-
  106        synprop_scope(P,Scope),
  107        triple_axiom_annotation(E,P,V,oio:hasDbXref,Xref).
 entity_xref_src(?Cls:atm, ?X:str, ?S:str)
true if Cls has X as an xref, and axiom annotated with S
  114entity_xref_src(C,X) :-
  115        entity_xref_src(C,X,_).
  116entity_xref_src(C,X,S) :-
  117        entity_xref_src(C,X,_,S).
  118entity_xref_src(C,X,A,S) :-
  119        has_dbxref_axiom(C,X,A),
  120        rdf(A,oio:source,S).
  121
  122%!  entity_xref_prefix(?Cls:atm, ?X:str, ?Pre:str)
  123%
  124%   true if Cls has X as an xref, and X has prefix Pre
  125%
  126:- rdf_meta entity_xref_prefix(r,o,o).
  127entity_xref_prefix(C,X,P) :-
  128        has_dbxref(C,X),
  129        curie_prefix(X,P).
  132one_to_one_xref(E,X,S) :-
  133        entity_xref_idspace(E,X,S),
  134        \+ ((entity_xref_idspace(E,X2,S),
  135             X2\=X)),
  136        \+ ((entity_xref_idspace(E2,X,S),
  137             E2\=E)).
  138
  139non_one_to_one_xref(E,X,S) :-
  140        entity_xref_idspace(E,X,S),
  141        \+ one_to_one_xref(E,X,S).
  142
  143one_to_many_xref(E,X,S) :-
  144        one_to_many_xref(E,X,S,_).
  145one_to_many_xref(E,X,S,X2) :-
  146        entity_xref_idspace(E,X,S),
  147        entity_xref_idspace(E,X2,S),
  148        X2\=X.
  149
  150many_to_one_xref(E,X,S) :-
  151        many_to_one_xref(E,X,S,_).
  152many_to_one_xref(E,X,S,E2) :-
  153        entity_xref_idspace(E,X,S),
  154        entity_xref_idspace(E2,X,S),
  155        E2\=E.
  156
  157many_to_many_xref(E,X,S,E2,X2) :-
  158        many_to_one_xref(E,X,S,X2),
  159        one_to_many_xref(E,X,S,E2).
  160
  161many_to_many_xref(E,X,S) :-
  162        entity_xref_idspace(E,X,S),
  163        \+ \+ many_to_one_xref(E,X,S),
  164        \+ \+ one_to_many_xref(E,X,S)