1:-use_module(library(trill)).    2
    3:- trill. % or :- trillp. or :- tornado.
    4
    5/*
    6This knowledge base is inpired by the people+pets ontology from
    7Patel-Schneider, P, F., Horrocks, I., and Bechhofer, S. 2003. Tutorial on OWL.
    8The knowledge base indicates that the individuals that own an animal which is a pet are nature lovers, from
    9Zese, R.: Reasoning with Probabilistic Logics. ArXiv e-prints 1405.0915v3. 
   10Doctoral Consortium of the 30th International Conference on Logic Programming (ICLP 2014), July 19-22, Vienna, Austria.
   11*/

?- prob_instanceOf('natureLover','Kevin',Prob). ?- instanceOf('natureLover','Kevin',ListExpl).

*/

   20owl_rdf('<?xml version="1.0"?>
   21
   22<!DOCTYPE rdf:RDF [
   23    <!ENTITY owl "http://www.w3.org/2002/07/owl#" >
   24    <!ENTITY xsd "http://www.w3.org/2001/XMLSchema#" >
   25    <!ENTITY rdfs "http://www.w3.org/2000/01/rdf-schema#" >
   26    <!ENTITY rdf "http://www.w3.org/1999/02/22-rdf-syntax-ns#" >
   27    <!ENTITY disponte "https://sites.google.com/a/unife.it/ml/disponte#" >
   28]>
   29
   30
   31<rdf:RDF xmlns="http://cohse.semanticweb.org/ontologies/people#"
   32     xml:base="http://cohse.semanticweb.org/ontologies/people"
   33     xmlns:rdfs="http://www.w3.org/2000/01/rdf-schema#"
   34     xmlns:owl="http://www.w3.org/2002/07/owl#"
   35     xmlns:xsd="http://www.w3.org/2001/XMLSchema#"
   36     xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
   37     xmlns:disponte="https://sites.google.com/a/unife.it/ml/disponte#">
   38    <owl:Ontology rdf:about="http://cohse.semanticweb.org/ontologies/people"/>
   39    
   40
   41
   42    <!-- 
   43    ///////////////////////////////////////////////////////////////////////////////////////
   44    //
   45    // Annotation properties
   46    //
   47    ///////////////////////////////////////////////////////////////////////////////////////
   48     -->
   49
   50    
   51
   52
   53    <!-- https://sites.google.com/a/unife.it/ml/disponte#probability -->
   54
   55    <owl:AnnotationProperty rdf:about="&disponte;probability"/>
   56    
   57
   58
   59    <!-- 
   60    ///////////////////////////////////////////////////////////////////////////////////////
   61    //
   62    // Object Properties
   63    //
   64    ///////////////////////////////////////////////////////////////////////////////////////
   65     -->
   66
   67    
   68
   69
   70    <!-- http://cohse.semanticweb.org/ontologies/people#has_animal -->
   71
   72    <owl:ObjectProperty rdf:about="http://cohse.semanticweb.org/ontologies/people#has_animal">
   73        <rdfs:label>has_animal</rdfs:label>
   74        <rdfs:comment></rdfs:comment>
   75    </owl:ObjectProperty>
   76    
   77
   78
   79    <!-- 
   80    ///////////////////////////////////////////////////////////////////////////////////////
   81    //
   82    // Classes
   83    //
   84    ///////////////////////////////////////////////////////////////////////////////////////
   85     -->
   86
   87    
   88
   89
   90    <!-- http://cohse.semanticweb.org/ontologies/people#cat -->
   91
   92    <!--owl:Class rdf:about="http://cohse.semanticweb.org/ontologies/people#cat">
   93        <rdfs:label>cat</rdfs:label>
   94        <rdfs:subClassOf rdf:resource="http://cohse.semanticweb.org/ontologies/people#pet"/>
   95        <rdfs:comment></rdfs:comment>
   96    </owl:Class>
   97    <owl:Axiom>
   98        <disponte:probability rdf:datatype="&xsd;decimal">0.6</disponte:probability>
   99        <owl:annotatedSource rdf:resource="http://cohse.semanticweb.org/ontologies/people#cat"/>
  100        <owl:annotatedTarget rdf:resource="http://cohse.semanticweb.org/ontologies/people#pet"/>
  101        <owl:annotatedProperty rdf:resource="&rdfs;subClassOf"/>
  102    </owl:Axiom-->
  103        
  104    
  105
  106
  107    <!-- http://cohse.semanticweb.org/ontologies/people#dog -->
  108    
  109    <owl:Class rdf:about="http://cohse.semanticweb.org/ontologies/people#dog">
  110        <rdfs:label>cat</rdfs:label>
  111        <rdfs:subClassOf rdf:resource="http://cohse.semanticweb.org/ontologies/people#pet"/>
  112        <rdfs:comment></rdfs:comment>
  113    </owl:Class>
  114        
  115    
  116
  117
  118    <!-- http://cohse.semanticweb.org/ontologies/people#natureLover -->
  119
  120    <owl:Class rdf:about="http://cohse.semanticweb.org/ontologies/people#natureLover"/>
  121    
  122
  123
  124    <!-- http://cohse.semanticweb.org/ontologies/people#pet -->
  125
  126    <owl:Class rdf:about="http://cohse.semanticweb.org/ontologies/people#pet"/>
  127    
  128
  129
  130    <!-- 
  131    ///////////////////////////////////////////////////////////////////////////////////////
  132    //
  133    // Individuals
  134    //
  135    ///////////////////////////////////////////////////////////////////////////////////////
  136     -->
  137
  138    
  139
  140
  141    <!-- http://cohse.semanticweb.org/ontologies/people#Fluffy -->
  142
  143    <owl:NamedIndividual rdf:about="http://cohse.semanticweb.org/ontologies/people#Fluffy">
  144        <rdf:type rdf:resource="http://cohse.semanticweb.org/ontologies/people#cat"/>
  145        <rdfs:label>Fuffy</rdfs:label>
  146        <rdfs:comment></rdfs:comment>
  147    </owl:NamedIndividual>
  148    <owl:Axiom>
  149        <disponte:probability>0.4</disponte:probability>
  150        <owl:annotatedSource rdf:resource="http://cohse.semanticweb.org/ontologies/people#Fluffy"/>
  151        <owl:annotatedTarget rdf:resource="http://cohse.semanticweb.org/ontologies/people#cat"/>
  152        <owl:annotatedProperty rdf:resource="&rdf;type"/>
  153    </owl:Axiom>
  154    
  155
  156
  157    <!-- http://cohse.semanticweb.org/ontologies/people#Kevin -->
  158
  159    <owl:NamedIndividual rdf:about="http://cohse.semanticweb.org/ontologies/people#Kevin">
  160        <rdfs:label>Kevin</rdfs:label>
  161        <rdfs:comment></rdfs:comment>
  162        <has_animal rdf:resource="http://cohse.semanticweb.org/ontologies/people#Fluffy"/>
  163        <has_animal rdf:resource="http://cohse.semanticweb.org/ontologies/people#Tom"/>
  164    </owl:NamedIndividual>
  165    
  166
  167
  168    <!-- http://cohse.semanticweb.org/ontologies/people#Tom -->
  169
  170    <owl:NamedIndividual rdf:about="http://cohse.semanticweb.org/ontologies/people#Tom">
  171        <rdf:type rdf:resource="http://cohse.semanticweb.org/ontologies/people#cat"/>
  172        <rdfs:label>Tom</rdfs:label>
  173        <rdfs:comment></rdfs:comment>
  174    </owl:NamedIndividual>
  175    <owl:Axiom>
  176        <disponte:probability>0.3</disponte:probability>
  177        <owl:annotatedSource rdf:resource="http://cohse.semanticweb.org/ontologies/people#Tom"/>
  178        <owl:annotatedTarget rdf:resource="http://cohse.semanticweb.org/ontologies/people#cat"/>
  179        <owl:annotatedProperty rdf:resource="&rdf;type"/>
  180    </owl:Axiom>
  181    
  182
  183    <!-- http://cohse.semanticweb.org/ontologies/people#Dino -->
  184
  185    <owl:NamedIndividual rdf:about="http://cohse.semanticweb.org/ontologies/people#Dino">
  186        <rdf:type rdf:resource="http://cohse.semanticweb.org/ontologies/people#dinosaur"/>
  187        <rdfs:label>Dino</rdfs:label>
  188        <rdfs:comment></rdfs:comment>
  189    </owl:NamedIndividual>
  190    
  191
  192
  193    <!-- http://cohse.semanticweb.org/ontologies/people#Fred -->
  194
  195    <owl:NamedIndividual rdf:about="http://cohse.semanticweb.org/ontologies/people#Fred">
  196        <rdfs:label>Kevin</rdfs:label>
  197        <rdfs:comment></rdfs:comment>
  198        <has_animal rdf:resource="http://cohse.semanticweb.org/ontologies/people#Dino"/>
  199    </owl:NamedIndividual>
  200    
  201
  202
  203    <!-- http://cohse.semanticweb.org/ontologies/people#Spike -->
  204
  205    <owl:NamedIndividual rdf:about="http://cohse.semanticweb.org/ontologies/people#Spike">
  206        <rdf:type rdf:resource="http://cohse.semanticweb.org/ontologies/people#dog"/>
  207        <rdfs:label>Spike</rdfs:label>
  208        <rdfs:comment></rdfs:comment>
  209        <is_animal_of rdf:resource="http://cohse.semanticweb.org/ontologies/people#Kevin"/>
  210    </owl:NamedIndividual>
  211    
  212    
  213
  214    <!-- 
  215    ///////////////////////////////////////////////////////////////////////////////////////
  216    //
  217    // General axioms
  218    //
  219    ///////////////////////////////////////////////////////////////////////////////////////
  220     -->
  221
  222    <owl:Axiom>
  223        <owl:annotatedTarget rdf:resource="http://cohse.semanticweb.org/ontologies/people#natureLover"/>
  224        <owl:annotatedProperty rdf:resource="&rdfs;subClassOf"/>
  225        <owl:annotatedSource>
  226            <owl:Restriction>
  227                <rdfs:subClassOf rdf:resource="http://cohse.semanticweb.org/ontologies/people#natureLover"/>
  228                <owl:onProperty rdf:resource="http://cohse.semanticweb.org/ontologies/people#has_animal"/>
  229                <owl:someValuesFrom rdf:resource="http://cohse.semanticweb.org/ontologies/people#pet"/>
  230            </owl:Restriction>
  231        </owl:annotatedSource>
  232    </owl:Axiom>
  233</rdf:RDF>').
  234
  235subClassOf('cat','pet').
  236subClassOf('dinosaur','pet').
  237annotationAssertion('disponte:probability',subClassOf('cat','pet'),literal('0.6')).
  238annotationAssertion('disponte:probability',subClassOf('dog','pet'),literal('0.8')).
  239
  240inverseProperties('has_animal','is_animal_of')