Did you know ... Search Documentation:
Pack sparqlprog -- prolog/sparqlprog/owl_util.pl
PublicShow source

This module provides predicates for working with OWL ontologies. Although OWL ontologies can be accessed directly via rdf/3 triples, this can be quite a low level means of access, especially for ontologies employing constructs that map to multiple triples, including:

Note on use outside sparqlprog

Although this is distributed with sparqlprog, it can be used directly in conjunction with an in-memory triplestore.

 label_of(?Label, ?X) is nondet
 label_of(?Label, ?X, ?Lang) is nondet
 triple_axiom(T, A) is nondet
as triple_axiom/4, first argument is triple(I,P1,J)
 triple_axiom(?I, ?P, ?J, ?A) is nondet
 triple_axiom_annotation(?T, ?P, ?V) is nondet
as triple_axiom_annotation/5, first argument is triple(I,P1,J)
 triple_axiom_annotation(?I, ?P1, ?J, ?P, ?V) is nondet
 triple_axiom_annotations(?I, ?P, ?J, ?L) is nondet
 triple_property_axiom_annotations(?I, ?P, ?J, ?P1, ?L:list) is nondet
for a triple IPJ, yield all axiom annotation values for annotation property P1
 axiom_annotation(?Axiom, ?Property, ?Value) is nondet
Axiom is always a blank node

See https://www.w3.org/TR/owl2-primer/#Annotating_Axioms_and_Entities

 not_thing_class(?X) is nondet
true unless X is owl:Thing
 deprecated(?X) is nondet
true if X has a owl:deprecated axiom with value true
 owl_equivalent_class(?A, ?B) is nondet
inferred equivalent class between A and B, exploiting transitivity and symmetry
 owl_equivalent_class_asserted(?A, ?B) is nondet
only holds if the assertion is in the direction from A to B
 owl_equivalent_class_asserted_symm(?A, ?B) is nondet
inferred equivalent class between A and B, exploiting symmetry
 owl_equivalent_property_asserted_symm(?A, ?B) is nondet
inferred equivalent property between A and B, exploiting symmetry
 subclass_cycle(?A) is nondet
true if there is a path between A and A following one or more subClassOf links
 bnode_signature(?N, ?X) is nondet
true if X is in the signature of the construct defined by blank node N
 owl_some(?Restr, ?Property, ?Obj) is nondet
true if Restr is a blank node representing OWL expression SomeValuesFrom(Property,Obj)
 subclass_of_some(?Cls, ?Property, ?Obj) is nondet
true if Cls is a subclass of the expression SomeValuesFrom(Property,Obj)
 owl_all(?Restr, ?Property, ?Obj) is nondet
true if Restr is an OWL expression AllValuesFrom(Property,Obj)
 owl_node_info(+S, ?P, ?O, ?E) is nondet
find asserted or inferred triples for S
 class_genus(?C, ?G) is nondet
true if C EquivalentTo .... and .... and G and ...
 class_differentia(?C, ?P, ?Y) is nondet
true if C EquivalentTo .... and .... and (P some Y) and ...
 eq_intersection_member(?C, ?M) is nondet
true if C EquivalentTo .... and .... and M and ...
 intersection_member(?I, ?M) is nondet
true if I is a blank node representing an intersection, and M is a member of the list
 rdflist_member(?L, ?M) is nondet
see also rdfs_member/2

this is an alternate implementation that makes the expansion to an rdf list explicit

 common_ancestor(?X, ?Y, ?A) is nondet
MAY MOVE TO ANOTHER MODULE
 mrca(?X, ?Y, ?A) is nondet
most recent common ancestor

MAY MOVE TO ANOTHER MODULE

 common_descendant(?X, ?Y, ?D) is nondet
MAY MOVE TO ANOTHER MODULE
 mrcd(?X, ?Y, ?D) is nondet
MAY MOVE TO ANOTHER MODULE
 egraph_common_ancestor(?X, ?Y, ?A) is nondet
version of common_ancestor/3 for graphs that have entailments materialized (egraphs)

MAY MOVE TO ANOTHER MODULE

 egraph_mrca(?X, ?Y, ?A) is nondet
version of mrca/3 for graphs that have entailments materialized (egraphs)

MAY MOVE TO ANOTHER MODULE

 owl_edge(?S, ?P, ?O, ?G) is nondet
 owl_edge(?S, ?P, ?O) is nondet
An edge in an existential graph

Either: S SubClassOf O Or: S SubClassOf P some O Or: S EquivalentTo O Or: S type O

 owl_subgraph(+Nodes:list, +Preds:list, ?Quads:list, +Opts:list) is det
traverses owl edge graph starting from a predefined set of nodes
 extract_subontology(?Objs, ?G, ?Opts) is nondet
 quads_objects(?Quads, ?Objs) is nondet
 quads_dict(?Quads, ?Dict) is nondet
generates a OBO JSON object from a set of triples or quads

Quads = [rdf(S,P,O,G), ...]

 ensure_curie(+Uri, ?CurieOrUriTerm) is det
translates URI to a CurieOrUriTerm
 subsumed_prefix_namespace(?Pre, ?NS, ?Pre2, ?NS2) is nondet
 ensure_uri(+CurieOrUriTerm, ?Uri) is det
translates CurieOrUriTerm to a URI. CurieOrUriTerm is either:
  • a Uri atom
  • a Pre:Post CURIE term
  • an atom of the form 'Pre:Post'
 simj_by_subclass(?C1, ?C2, ?S) is nondet
 simj_by_subclass(?C1, ?C2, ?S, ?N1, ?N2) is nondet
 owl_assert_axiom(+Axiom, ?MainTriple, +Graph:iri) is det
 owl_assert_axiom(+Axiom, +Graph:iri) is det
 owl_assert_axiom(+Axiom) is det
asserts an axiom
 owl_assert_axiom_with_anns(+Axiom, ?MainTriple, +Graph:iri, +Annotations:list) is det
 owl_assert_axiom_with_anns(+Axiom, +Graph:iri, +Annotations:list) is det
Annotations = [annotation(P1,V1), ...]

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 is_en(Arg1)
 enlabel_of(Arg1, Arg2)
 literal_atom(Arg1, Arg2)
 instantiated_class(Arg1)
 declare_shacl_prefixes
 thing_class(Arg1)
 inferred_type(Arg1, Arg2)
 owl_edge(Arg1, Arg2, Arg3)
 owl_edge_ancestor(Arg1, Arg2)
 owl_edge_ancestor(Arg1, Arg2, Arg3)
 assert_named_individuals
 assert_named_individuals_forall
 owl_assert_axiom(Arg1)
 owl_assert_axiom(Arg1, Arg2)
 owl_assert_axiom_with_anns(Arg1, Arg2, Arg3)
 label(Arg1, Arg2)
 subClassOf(Arg1, Arg2)