14
15
16:- module(simplify_axiom, [
17 simplify_axiom/2
18 ]).
49simplify_axiom(
50 'ClassAssertion'('ObjectSomeValuesFrom'(OPE, 'ObjectOneOf'([I2])), I1),
51 'ObjectPropertyAssertion'(OPE, I1, I2)
52 ) :- !.
53
55simplify_axiom(
56 'ClassAssertion'('DataHasValue'(DPE, Data), I1),
57 'DataPropertyAssertion'(DPE, I1, Data)
58 ) :- !.
59
61simplify_axiom(
62 'ClassAssertion'('ObjectOneOf'([I2]), I1),
63 'SameIndividual'([I1, I2])
64 ) :- !.
65
67simplify_axiom(
68 'SubClassOf'(CE1, 'ObjectComplementOf'(CE2)),
69 'DisjointClasses'([CE1, CE2])
70 ) :- !.
71
73simplify_axiom(
74 'SubClassOf'('ObjectIntersectionOf'([owl:'Thing', 'ObjectSomeValuesFrom'('ObjectInverseOf'(OPE), owl:'Thing')]), CE),
75 'ObjectPropertyRange'(OPE, CE)
76 ) :- !.
77
78simplify_axiom(
79 'SubClassOf'('ObjectSomeValuesFrom'('ObjectInverseOf'(OPE), owl:'Thing'), CE),
80 'ObjectPropertyRange'(OPE, CE)
81 ) :- !.
82
84simplify_axiom(
85 'SubClassOf'('ObjectIntersectionOf'([owl:'Thing', 'ObjectSomeValuesFrom'(OPE, owl:'Thing')]), CE),
86 'ObjectPropertyDomain'(OPE, CE)
87 ) :- !.
88
89simplify_axiom(
90 'SubClassOf'('ObjectSomeValuesFrom'(OPE, owl:'Thing'), CE),
91 'ObjectPropertyDomain'(OPE, CE)
92 ) :- !.
93
98simplify_axiom(
99 'SubObjectPropertyOf'('ObjectPropertyChain'(['ObjectInverseOf'(R)]), 'ObjectInverseOf'(S)),
100 'SubObjectPropertyOf'(R, S)
101 ) :- !.
102
103simplify_axiom(
104 'SubObjectPropertyOf'('ObjectPropertyChain'(['ObjectInverseOf'(R)]), S),
105 'SubObjectPropertyOf'(R, 'ObjectInverseOf'(S))
106 ) :- !.
107
108simplify_axiom(
109 'SubObjectPropertyOf'('ObjectPropertyChain'([R]), S),
110 'SubObjectPropertyOf'(R, S)
111 ) :- !.
112
113simplify_axiom(
114 'SubObjectPropertyOf'('ObjectPropertyChain'([R, R]), R),
115 'TransitiveObjectProperty'(R)
116 ) :- !.
117
118
120simplify_axiom(Axiom, Axiom)
Maps the given axiom to a syntactically simpler form
The given axiom is mapped to a syntactically simpler form in order to achieve better compatibility with OWL tools and OWL fragments (which are defined based on syntax). In most cases the axiom is preserved as it is, we only target the following forms:
*/