1:-use_module(library(trill)).    2
    3:- trill. % or :- trillp. or :- tornado.

?- instanceOf(person,john,Expl).

*/

   11owl_rdf('<?xml version="1.0"?>
   12<rdf:RDF xmlns="http://example.foo#"
   13     xml:base="http://example.foo"
   14     xmlns:johnEmployee="http://example.foo#"
   15     xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
   16     xmlns:owl="http://www.w3.org/2002/07/owl#"
   17     xmlns:xml="http://www.w3.org/XML/1998/namespace"
   18     xmlns:xsd="http://www.w3.org/2001/XMLSchema#"
   19     xmlns:rdfs="http://www.w3.org/2000/01/rdf-schema#">
   20    <owl:Ontology rdf:about="http://example.foo"/>
   21
   22    <!-- Classes -->
   23    <owl:Class rdf:about="http://example.foo#worker">
   24        <rdfs:subClassOf rdf:resource="http://example.foo#person"/>
   25    </owl:Class>
   26
   27</rdf:RDF>').
   28subClassOf('johnEmployee:employee','johnEmployee:worker').
   29owl_rdf('<?xml version="1.0"?>
   30<rdf:RDF xmlns="http://example.foo#"
   31     xml:base="http://example.foo"
   32     xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
   33     xmlns:owl="http://www.w3.org/2002/07/owl#"
   34     xmlns:xml="http://www.w3.org/XML/1998/namespace"
   35     xmlns:xsd="http://www.w3.org/2001/XMLSchema#"
   36     xmlns:rdfs="http://www.w3.org/2000/01/rdf-schema#">
   37    <owl:Ontology rdf:about="http://example.foo"/>
   38    
   39    <!-- Individuals -->
   40    <owl:NamedIndividual rdf:about="http://example.foo#john">
   41        <rdf:type rdf:resource="http://example.foo#employee"/>
   42    </owl:NamedIndividual>
   43</rdf:RDF>')