trill_2_manch

This module translates TRILL format into OWL manchester syntax.

author
- Riccardo Zese
license
- Artistic License 2.0
   10:- module(trill_2_manch, [convert_explanations/2, convert_axiom/2]).   11
   12% simple: some better rendering
   13% full:   full Manchester Syntax recommendation TODO
   14trill_2_manch_setting(convertion_mode(simple)).
   15
   16% class(?IRI)
   17prolog2manchester(class(IRI), ClFunc):- 
   18  iri(IRI,IRIF),
   19  appendManchester1('Class', [IRIF], ClFunc). 
   20
   21% datatype(?IRI)
   22prolog2manchester(datatype(IRI), DtFunc):- 
   23  iri(IRI,IRIF),
   24  appendManchester1('Datatype', [IRIF], DtFunc).
   25
   26% objectProperty(?IRI)
   27prolog2manchester(objectProperty(IRI), OpFunc) :-
   28  iri(IRI,IRIF),
   29  appendManchester1('ObjectProperty', [IRIF], OpFunc).
   30
   31% dataProperty(?IRI)
   32prolog2manchester(dataPropery(IRI), DPFunc):- 
   33  iri(IRI,IRIF),
   34  appendManchester1('Dataproperty', [IRIF], DPFunc).
   35
   36% annotationProperty(?IRI)
   37prolog2manchester(annotationProperty(IRI), APFunc ):- 
   38  iri(IRI,IRIF),
   39  appendManchester1('AnnotationProperty', [IRIF], APFunc).
   40
   41% namedIndividual(?IRI)
   42prolog2manchester(namedIndividual(IRI), NIFunc):- 
   43  iri(IRI,IRIF),
   44  appendManchester1('Individual', [IRIF], NIFunc).
   45
   46% anonymousIndividual(?IRI)
   47prolog2manchester(anonymousIndividual(IRI), AIFunc):- 
   48  iri(IRI,IRIF),
   49  appendManchester1('Individual', [IRIF], AIFunc).
   50
   51
   52/* ClassExpression e PropertyExpression */
   53
   54% subClassOf(?SubClass:ClassExpression, ?SuperClass:ClassExpression)
   55prolog2manchester(subClassOf(ClassExpression1, ClassExpression2), SCFunc):- %appendManchester SubClassOf ClassExpressionFunctional1 ClassExpressionFunctional2 
   56  classExpression2manchester(ClassExpression1,ClassExpressionFunctional1),
   57  classExpression2manchester(ClassExpression2,ClassExpressionFunctional2), 
   58  (trill_2_manch_setting(convertion_mode(simple)) ->
   59    appendManchester2([ClassExpressionFunctional1, 'subClassOf', ClassExpressionFunctional2],SCFunc) ;
   60    ( appendManchester('Class',[ClassExpressionFunctional1],SCFunc0),
   61      appendManchester('SubClassOf',[ClassExpressionFunctional2],SCFunc1),
   62      appendManchester2([SCFunc0, SCFunc1],SCFunc)
   63    )
   64  ).
   65
   66% equivalentClasses(?ClassExpressions:set(ClassExpression))
   67prolog2manchester(equivalentClasses(ListaClassExpression), ECFunc):-  %'EquivalentClasses(axiomAnnotations, ClassExpression, ClassExpression { ClassExpression } )'):-
   68  findall(CEF,(member(CE,ListaClassExpression),classExpression2manchester(CE,CEF)),L),
   69  (length(L,2) ->
   70    ( L = [C1,C2],
   71      (trill_2_manch_setting(convertion_mode(simple)) ->
   72       appendManchester2([C1,'equivalentTo',C2],ECFunc) ;
   73       ( appendManchester('Class',[C1],SCFunc0),
   74         appendManchester('EquivalentTo',[C2],SCFunc1),
   75         appendManchester2([SCFunc0, SCFunc1],ECFunc)
   76       )
   77      )
   78    )
   79    ;
   80    ( trill_2_manch_setting(convertion_mode(simple)) ->
   81       appendManchester3('EquivalentTo',L,ECFunc);
   82       appendManchester('EquivalentTo',L,ECFunc)
   83    )
   84  ).
   85
   86% disjointClasses(?ClassExpressions:set(ClassExpression))
   87prolog2manchester(disjointClasses(ListaClassExpression), ECFunc):- %'DisjointClasses(axiomAnnotations, ClassExpression, ClassExpression { ClassExpression })'). 
   88  findall(CEF,(member(CE,ListaClassExpression),classExpression2manchester(CE,CEF)),L),
   89  (length(L,2) ->
   90    ( L = [C1,C2],
   91      (trill_2_manch_setting(convertion_mode(simple)) ->
   92       appendManchester2([C1,'disjointWith',C2],ECFunc) ;
   93       ( appendManchester('Class',[C1],SCFunc0),
   94         appendManchester('DisjointWith',[C2],SCFunc1),
   95         appendManchester2([SCFunc0, SCFunc1],ECFunc)
   96       )
   97      )
   98    )
   99    ;
  100    ( trill_2_manch_setting(convertion_mode(simple)) ->
  101        appendManchester3('DisjointWith',L,ECFunc);
  102        appendManchester('DisjointWith',L,ECFunc)
  103    )
  104  ).
  105
  106% disjointUnion(?ClassExpression, ?ClassExpressions:set(ClassExpression))
  107prolog2manchester(disjointUnion(IRI,ListaClassExpression), ECFunc):- %'DisjointUnion(axiomAnnotations, Class disjointClassExpressions)'% disjointClassExpressions := ClassExpression ClassExpression { ClassExpression })
  108  classExpression2manchester(IRI,ClassExpressionFunctional),
  109  objectUnionOf(ListaClassExpression, LM),
  110  (trill_2_manch_setting(convertion_mode(simple)) ->
  111    appendManchester2([ClassExpressionFunctional,'disjointWith',LM],ECFunc)
  112    ;
  113    (
  114      appendManchester('Class',[ClassExpressionFunctional],SCFunc0),
  115      appendManchester('DisjointWith',[LM],SCFunc1),
  116      appendManchester2([SCFunc0, SCFunc1],ECFunc)
  117    )
  118  ).
  119
  120% subPropertyOf(?Sub:PropertyExpression, ?Super:ObjectPropertyExpression)
  121prolog2manchester(subPropertyOf(PropertyExpression1, PropertyExpression2), SPFunc):- 
  122  propertyExpression2manchester(PropertyExpression1,PropertyExpressionFunctional1),
  123  propertyExpression2manchester(PropertyExpression2,PropertyExpressionFunctional2),
  124  (trill_2_manch_setting(convertion_mode(simple)) ->
  125    appendManchester([PropertyExpressionFunctional1, 'subPropertyOf', PropertyExpressionFunctional2],SPFunc) ;
  126    ( appendManchester('ObjectProperty',[PropertyExpressionFunctional1],SPFunc0),
  127      appendManchester('SubPropertyOf',[PropertyExpressionFunctional1],SPFunc1),
  128      appendManchester2([SPFunc0, SPFunc1],SPFunc)
  129    )
  130  ).
  131
  132% equivalentProperties(?PropertyExpressions:set(PropertyExpression))  
  133prolog2manchester(equivalentProperties(ListaPropertyExpression), EPFunc):- %'EquivalentObjectProperties(axiomAnnotations, ObjectPropertyExpression, ObjectPropertyExpression { ObjectPropertyExpression })').
  134  findall(PEF,(member(PE,ListaPropertyExpression), propertyExpression2manchester(PE,PEF)),L),
  135  (length(L,2) ->
  136    ( L = [P1,P2],
  137      (trill_2_manch_setting(convertion_mode(simple)) ->
  138       appendManchester2([P1,'equivalentTo',P2],EPFunc) ;
  139       ( appendManchester('ObjectProperty',[P1],SPFunc0),
  140         appendManchester('EquivalentTo',[P2],SPFunc1),
  141         appendManchester2([SPFunc0, SPFunc1],EPFunc)
  142       )
  143      )
  144    )
  145    ;
  146    ( trill_2_manch_setting(convertion_mode(simple)) ->
  147       appendManchester3('EquivalentTo',L,EPFunc);
  148       appendManchester('EquivalentTo',L,EPFunc)
  149    )
  150  ).
  151
  152% disjointProperties(?PropertyExpressions:set(PropertyExpression))                
  153prolog2manchester(dijointProperties(ListaPropertyExpression), DPFunc):- %'DisjointObjectProperties(axiomAnnotations, ObjectPropertyExpression, ObjectPropertyExpression { ObjectPropertyExpression })').
  154  findall(PEF,(member(PE, ListaPropertyExpression), propertyExpression2manchester(PE,PEF)),L),
  155  (length(L,2) ->
  156    ( L = [P1,P2],
  157      (trill_2_manch_setting(convertion_mode(simple)) ->
  158       appendManchester2([P1,'disjointWith',P2],DPFunc) ;
  159       ( appendManchester('ObjectProperty',[P1],SPFunc0),
  160         appendManchester('DisjointWith',[P2],SPFunc1),
  161         appendManchester2([SPFunc0, SPFunc1],DPFunc)
  162       )
  163      )
  164    )
  165    ;
  166    ( trill_2_manch_setting(convertion_mode(simple)) ->
  167       appendManchester3('DisjointWith',L,DPFunc);
  168       appendManchester('DisjointWith',L,DPFunc)
  169    )
  170  ).
  171
  172% inverseProperties(?ObjectPropertyExpression1:ObjectPropertyExpression, ?ObjectPropertyExpression2:ObjectPropertyExpression)
  173prolog2manchester(inverseProperties(ObjectPropertyExpression1, ObjectPropertyExpression2), IOPFunc):- %'InverseObjectProperties(axiomAnnotations, ObjectPropertyExpression, ObjectPropertyExpression)'). 
  174  propertyExpression2manchester(ObjectPropertyExpression1,ObjectPropertyExpressionFunctional1),
  175  propertyExpression2manchester(ObjectPropertyExpression2,ObjectPropertyExpressionFunctional2), %appendManchester SubClassOf ClassExpressionFunctional1 ClassExpressionFunctional2
  176  (trill_2_manch_setting(convertion_mode(simple)) ->
  177    appendManchester2([ObjectPropertyExpressionFunctional1, 'inverseOf',ObjectPropertyExpressionFunctional2],IOPFunc);
  178    ( appendManchester('ObjectProperty',[ObjectPropertyExpression1],IOPFunc0),
  179      appendManchester('Inverse',[ObjectPropertyExpression2],IOPFunc1),
  180      appendManchester2([IOPFunc0, IOPFunc1],IOPFunc)
  181    )
  182  ).
  183
  184% propertyDomain(?PropertyExpression, ?CE)
  185prolog2manchester(propertyDomain(PropertyExpression, ClassExpression), OPDFunc):- %'ObjectPropertyDomain(axiomAnnotations, ObjectPropertyExpression, ClassExpression)').
  186  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  187  classExpression2manchester(ClassExpression,ClassExpressionF),
  188  (trill_2_manch_setting(convertion_mode(simple)) ->
  189    appendManchester2([PropertyExpressionF, 'domain',ClassExpressionF],OPDFunc);
  190    ( appendManchester('ObjectProperty',[PropertyExpressionF],OPDFunc0),
  191      appendManchester('Domain',[ClassExpressionF],OPDFunc1),
  192      appendManchester2([OPDFunc0, OPDFunc1],OPDFunc)
  193    )
  194  ).
  195
  196% propertyRange(?PropertyExpression, ?ClassExpression)
  197prolog2manchester(propertyRange(PropertyExpression, ClassExpression), OPRFunc) :- %'ObjectPropertyRange(axiomAnnotations, ObjectPropertyExpression, ClassExpression)').
  198  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  199  classExpression2manchester(ClassExpression,ClassExpressionF),
  200  (trill_2_manch_setting(convertion_mode(simple)) ->
  201    appendManchester2([PropertyExpressionF, 'range',ClassExpressionF],OPRFunc);
  202    ( appendManchester('ObjectProperty',[PropertyExpressionF],OPRFunc0),
  203      appendManchester('Range',[ClassExpressionF],OPRFunc1),
  204      appendManchester2([OPRFunc0, OPRFunc1],OPRFunc)
  205    )
  206  ).
  207
  208% functionalProperty(?PropertyExpression)
  209prolog2manchester(functionalProperty(PropertyExpression),FOPFunc) :- %'FunctionalObjectProperty(axiomAnnotations, ObjectPropertyExpression)'). %?
  210  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  211  (trill_2_manch_setting(convertion_mode(simple)) ->
  212    appendManchester2([PropertyExpressionF, 'functional'],FOPFunc);
  213    ( appendManchester('ObjectProperty',[PropertyExpressionF],FOPFunc0),
  214      appendManchester('Characteristic','Functional',FOPFunc1),
  215      appendManchester2([FOPFunc0, FOPFunc1],FOPFunc)
  216    )
  217  ).
  218
  219% inverseFunctionalProperty(?ObjectPropertyExpression)
  220prolog2manchester(inverseFunctionalProperty(PropertyExpression), IFPFunc):- %'InverseFunctionalObjectProperty(axiomAnnotations, ObjectPropertyExpression').
  221  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  222  (trill_2_manch_setting(convertion_mode(simple)) ->
  223    appendManchester2([PropertyExpressionF, 'inverseFunctional'],IFPFunc);
  224    ( appendManchester('ObjectProperty',[PropertyExpressionF],IFPFunc0),
  225      appendManchester('Characteristic','InverseFunctional',IFPFunc1),
  226      appendManchester2([IFPFunc0, IFPFunc1],IFPFunc)
  227    )
  228  ).
  229
  230% reflexiveProperty(?ObjectPropertyExpression)
  231prolog2manchester(reflexiveProperty(PropertyExpression), RPFunc) :- % ReflexiveObjectProperty(axiomAnnotations, ObjectPropertyExpression)'). 
  232  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  233  (trill_2_manch_setting(convertion_mode(simple)) ->
  234    appendManchester2([PropertyExpressionF, 'reflexive'],RPFunc);
  235    ( appendManchester('ObjectProperty',[PropertyExpressionF],RPFunc0),
  236      appendManchester('Characteristic','Reflexive',RPFunc1),
  237      appendManchester2([RPFunc0, RPFunc1],RPFunc)
  238    )
  239  ).
  240
  241% irreflexiveProperty(?ObjectPropertyExpression)
  242prolog2manchester(irreflexiveProperty(PropertyExpression), IOPFunc):- %'IrreflexiveObjectProperty(axiomAnnotations, ObjectPropertyExpression)').  
  243  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  244  (trill_2_manch_setting(convertion_mode(simple)) ->
  245    appendManchester2([PropertyExpressionF, 'irreflexive'],IOPFunc);
  246    ( appendManchester('ObjectProperty',[PropertyExpressionF],IOPFunc0),
  247      appendManchester('Characteristic','Irreflexive',IOPFunc1),
  248      appendManchester2([IOPFunc0, IOPFunc1],IOPFunc)
  249    )
  250  ).
  251
  252% symmetricProperty(?ObjectPropertyExpression)
  253prolog2manchester(symmetricProperty(PropertyExpression), SOPFunc) :- %'SymmetricObjectProperty(axiomAnnotations, ObjectPropertyExpression)').              
  254  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  255  (trill_2_manch_setting(convertion_mode(simple)) ->
  256    appendManchester2([PropertyExpressionF, 'symmetric'],SOPFunc);
  257    ( appendManchester('ObjectProperty',[PropertyExpressionF],SOPFunc0),
  258      appendManchester('Characteristic','Symmetric',SOPFunc1),
  259      appendManchester2([SOPFunc0, SOPFunc1],SOPFunc)
  260    )
  261  ).
  262
  263% asymmetricProperty(?ObjectPropertyExpression)
  264prolog2manchester(asymmetricProperty(PropertyExpression), AOPFunc):- %'AsymmetricObjectProperty(axiomAnnotations, ObjectPropertyExpression)').             
  265  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  266  (trill_2_manch_setting(convertion_mode(simple)) ->
  267    appendManchester2([PropertyExpressionF, 'asymmetric'],AOPFunc);
  268    ( appendManchester('ObjectProperty',[PropertyExpressionF],AOPFunc0),
  269      appendManchester('Characteristic','Asymmetric',AOPFunc1),
  270      appendManchester2([AOPFunc0, AOPFunc1],AOPFunc)
  271    )
  272  ).
  273
  274% transitiveProperty(?ObjectPropertyExpression)
  275prolog2manchester(transitiveProperty(PropertyExpression), TOPFunc):- %'TransitiveObjectProperty(axiomAnnotations, ObjectPropertyExpression)').
  276  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  277  (trill_2_manch_setting(convertion_mode(simple)) ->
  278    appendManchester2([PropertyExpressionF, 'transitive'],TOPFunc);
  279    ( appendManchester('ObjectProperty',[PropertyExpressionF],TOPFunc0),
  280      appendManchester('Characteristic','Transitive',TOPFunc1),
  281      appendManchester2([TOPFunc0, TOPFunc1],TOPFunc)
  282    )
  283  ).
  284
  285% hasKey(?ClassExpression,?PropertyExpression)
  286prolog2manchester(hasKey(ClassExpression,PropertyExpression), HKFunc):- %'HasKey(axiomAnnotations ClassExpression({ ObjectPropertyExpression }) ({ DataPropertyExpression }))'). 
  287  classExpression2manchester(ClassExpression,ClassExpressionF),
  288  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  289  (trill_2_manch_setting(convertion_mode(simple)) ->
  290    appendManchester2([ClassExpressionF, 'hasKey', PropertyExpressionF],HKFunc) ;
  291    ( appendManchester('Class',[ClassExpressionF],HKFunc0),
  292      appendManchester('HasKey',[PropertyExpressionF],HKFunc1),
  293      appendManchester2([HKFunc0, HKFunc1],HKFunc)
  294    )
  295  ).
  296
  297
  298/* Individual */
  299
  300% sameIndividual(?Individuals:set(Individual))
  301prolog2manchester(sameIndividual(ListIndividual), SIFunc) :- %'SameIndividual(axiomAnnotations, Individual Individual { Individual })').
  302  findall(IEF,(member(IE, ListIndividual), individual2manchester(IE,IEF)),L),
  303  (length(L,2) ->
  304    ( L = [I1,I2],
  305      (trill_2_manch_setting(convertion_mode(simple)) ->
  306       appendManchester2([I1,'sameAs',I2],SIFunc) ;
  307       ( appendManchester('Individual',[I1],SIFunc0),
  308         appendManchester('SameAs',[I2],SIFunc1),
  309         appendManchester2([SIFunc0, SIFunc1],SIFunc)
  310       )
  311      )
  312    )
  313    ;
  314    (trill_2_manch_setting(convertion_mode(simple)) ->
  315      appendManchester3('SameIndividual',L,SIFunc);
  316      appendManchester('SameIndividual',L,SIFunc)
  317    )
  318  ).
  319
  320% differentIndividuals(?Individuals:set(Individual))               
  321prolog2manchester(differentIndividual(ListIndividual), DIFunc ) :- %'DifferentIndividuals(axiomAnnotations, Individual Individual { Individual })').
  322  findall(IEF,(member(IE, ListIndividual), individual2manchester(IE,IEF)),L),
  323  (length(L,2) ->
  324    ( L = [I1,I2],
  325      (trill_2_manch_setting(convertion_mode(simple)) ->
  326       appendManchester2([I1,'differentFrom',I2],DIFunc) ;
  327       ( appendManchester('Individual',[I1],DIFunc0),
  328         appendManchester('DifferentFrom',[I2],DIFunc1),
  329         appendManchester2([DIFunc0, DIFunc1],DIFunc)
  330       )
  331      )
  332    )
  333    ;
  334    (trill_2_manch_setting(convertion_mode(simple)) ->
  335      appendManchester3('DifferentIndividuals',L,DIFunc);
  336      appendManchester('DifferentIndividuals',L,DIFunc)
  337    )
  338  ).
  339
  340
  341/* Assertion */
  342
  343% classAssertion(?ClassExpression, ?Individual)               
  344prolog2manchester(classAssertion(ClassExpression, IndividualExpression), CAFunc) :- %'ClassAssertion(axiomAnnotations, ClassExpression Individual)').
  345  classExpression2manchester(ClassExpression,ClassExpressionF),
  346  individual2manchester(IndividualExpression,IndividualExpressionF),
  347  (trill_2_manch_setting(convertion_mode(simple)) ->
  348    appendManchester2([IndividualExpressionF, 'type', ClassExpressionF],CAFunc) ;
  349    ( appendManchester('Individual',[IndividualExpressionF],CAFunc0),
  350      appendManchester('Type',[ClassExpressionF],CAFunc1),
  351      appendManchester2([CAFunc0, CAFunc1],CAFunc)
  352    )
  353  ).
  354
  355% propertyAssertion(?PropertyExpression, ?SourceIndividual:Individual, ?TargetIndividual:Individual)               
  356prolog2manchester(propertyAssertion(PropertyExpression, IndividualExpression1, IndividualExpression2), OPAFunc ):- %'ObjectPropertyAssertion( axiomAnnotations, ObjectPropertyExpression, sourceIndividual, targetIndividual)'). 
  357  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  358  individual2manchester(IndividualExpression1, IndividualExpression1F),
  359  individual2manchester(IndividualExpression2, IndividualExpression2F),
  360  (trill_2_manch_setting(convertion_mode(simple)) ->
  361    appendManchester2([IndividualExpression1F, PropertyExpressionF, IndividualExpression2F],OPAFunc) ;
  362    ( appendManchester('Individual',[IndividualExpression1F],OPAFunc0),
  363      appendManchester('Fact',[PropertyExpressionF, IndividualExpression2F],OPAFunc1),
  364      appendManchester2([OPAFunc0, OPAFunc1],OPAFunc)
  365    )
  366  ).
  367
  368% negativePropertyAssertion(?PropertyExpression, ?SourceIndividual:Individual, ?TargetIndividual:Individual)
  369prolog2manchester(negativePropertyAssertion(PropertyExpression, IndividualExpression1, IndividualExpression2), NOPAFunc ):- %'NegativeObjectPropertyAssertion(axiomAnnotations, ObjectPropertyExpression, sourceIndividual, targetIndividual)'). 
  370  propertyExpression2manchester(PropertyExpression,PropertyExpressionF),
  371  individual2manchester(IndividualExpression1, IndividualExpression1F),
  372  individual2manchester(IndividualExpression2, IndividualExpression2F),
  373  (trill_2_manch_setting(convertion_mode(simple)) ->
  374    appendManchester2([IndividualExpression1F, PropertyExpressionF, IndividualExpression2F],NOPAFunc) ;
  375    ( appendManchester('Individual',[IndividualExpression1F],NOPAFunc0),
  376      appendManchester('Fact',['not', PropertyExpressionF, IndividualExpression2F],NOPAFunc1),
  377      appendManchester2([NOPAFunc0, NOPAFunc1],NOPAFunc)
  378    )
  379  ).
  380
  381
  382/* Annotation */ 
  383/* TODO
  384% annotationAssertion(?AnnotationProperty, ?AnnotationSubject, ?AnnotationValue)
  385prolog2manchester(annotationAssertion(AnnotationProperty, AnnotationSubject, AnnotationValue),AAFunc):- %'AnnotationAssertion(axiomAnnotations, AnnotationProperty, AnnotationSubject AnnotationValue)'.
  386  propertyExpression2manchester(AnnotationProperty, AnnotationPropertyF),
  387  propertyExpression2manchester(AnnotationSubject, AnnotationSubjectF),
  388  (
  389        % condition 
  390        iri(AnnotationValue,AnnotationValueF)
  391    ->
  392        % true 
  393        appendManchester('AnnotationAssertion', [AnnotationPropertyF,AnnotationSubjectF,AnnotationValueF], AAFunc)
  394    ;
  395        % false 
  396        (literal2manchester(AnnotationValue, AnnotationValueF),
  397        appendManchester1('AnnotationAssertion', [AnnotationPropertyF,AnnotationSubjectF,AnnotationValueF], AAFunc))
  398  ).
  399
  400% annotation(:IRI,?AnnotationProperty,?AnnotationValue)             
  401prolog2manchester(annotation(AnnotationProperty, AnnotationProperty, AnnotationValue), AFunc):-%(iri,annotationProperty,annotationValue),'Annotation(annotationAnnotations, AnnotationProperty, AnnotationValue)'
  402  propertyExpression2manchester(AnnotationProperty, AnnotationPropertyF),
  403  (
  404        % condition 
  405        iri(AnnotationValue,AnnotationValueF)
  406    ->
  407        % true 
  408        appendManchester('AnnotationAssertion', [AnnotationPropertyF,AnnotationPropertyF,AnnotationValueF], AFunc)
  409    ;
  410        % false 
  411        literal2manchester(AnnotationValue, AnnotationValueF),
  412        appendManchester1('AnnotationAssertion', [AnnotationPropertyF,AnnotationPropertyF,AnnotationValueF], AFunc)
  413  ).
  414*/
  415
  416/* Ontology */
  417
  418% ontology(?IRI)
  419prolog2manchester(ontology(IRI), OIFunc):- 
  420  iri(IRI,IRIM),
  421  get_ontology_imports(IRIs0),
  422  get_ontology_version(IRIs1),
  423  IRIs = [IRIM,IRIs1|IRIs0],
  424  appendManchester1('Ontology', IRIs, OIFunc).
  425
  426
  427% ontologyImport(?Ontology, ?IRI)
  428prolog2manchester(ontologyImport(ontology(IRI)), OIMFunc):- 
  429  iri(IRI,IRIM),
  430  appendManchester1('Import', [IRIM], OIMFunc).
  431
  432% ontologyVersionInfo(?Ontology, ?IRI)
  433prolog2manchester(ontologyVersionInfo(ontology(IRI), IRIM)):-
  434  iri(IRI,IRIM).
  435
  436
  437get_ontology_imports(IRIs0):-
  438  findall(ontologyImport(ontology(ImportIRI)), axiom(ontologyImport(ontology(ImportIRI))), ImpAxs),
  439  ( dif(ImpAxs,[]) ->  
  440     findall(ImportIRIM,(member(Ax,ImpAxs),prolog2manchester(Ax, ImportIRIM)), IRIs0) ; 
  441     IRIs0 = [] 
  442  ).
  443
  444get_ontology_version(IRIs1):-
  445  ( axiom(ontologyVersionInfo(ontology(VersIRI))) -> 
  446    (prolog2manchester(ontologyVersionInfo(ontology(VersIRI, VersIRIM))), IRIs1 = [VersIRIM]) ; 
  447     IRIs1 = []
  448  ).
  449
  450
  451
  452/*Class expression*/
  453
  454classExpression2manchester(CE,CEF):- 
  455  (iri(CE,CEF); 
  456  objectIntersectionOf(CE,CEF);
  457  objectSomeValuesFrom(CE,CEF); 
  458  objectUnionOf(CE, CEF);
  459  objectComplementOf(CE,CEF); 
  460  objectOneOf(CE,CEF);
  461  objectAllValuesFrom(CE,CEF); 
  462  objectHasValue(CE,CEF); 
  463  objectHasSelf(CE,CEF) ;
  464  objectMinCardinality(CE,CEF); 
  465  objectMaxCardinality(CE,CEF); 
  466  objectExactCardinality(CE,CEF); 
  467  dataSomeValuesFrom(CE,CEF);
  468  dataAllValuesFrom(CE,CEF); 
  469  dataHasValue(CE,CEF);
  470  dataMinCardinality(CE,CEF); 
  471  dataMaxCardinality(CE,CEF); 
  472  dataExactCardinality(CE,CEF)), 
  473  !.
  474
  475/*
  476ObjectIntersectionOf := 'ObjectIntersectionOf' '(' ClassExpression ClassExpression { ClassExpression } ')'
  477ObjectUnionOf := 'ObjectUnionOf' '(' ClassExpression ClassExpression { ClassExpression } ')'
  478ObjectComplementOf := 'ObjectComplementOf' '(' ClassExpression ')'
  479ObjectOneOf := 'ObjectOneOf' '(' Individual { Individual }')'
  480ObjectSomeValuesFrom := 'ObjectSomeValuesFrom' '(' ObjectPropertyExpression ClassExpression ')'
  481ObjectAllValuesFrom := 'ObjectAllValuesFrom' '(' ObjectPropertyExpression ClassExpression ')'
  482ObjectHasValue := 'ObjectHasValue' '(' ObjectPropertyExpression Individual ')'
  483ObjectHasSelf := 'ObjectHasSelf' '(' ObjectPropertyExpression ')'
  484ObjectMinCardinality := 'ObjectMinCardinality' '(' nonNegativeInteger ObjectPropertyExpression [ ClassExpression ] ')'
  485ObjectMaxCardinality := 'ObjectMaxCardinality' '(' nonNegativeInteger ObjectPropertyExpression [ ClassExpression ] ')'
  486ObjectExactCardinality := 'ObjectExactCardinality' '(' nonNegativeInteger ObjectPropertyExpression [ ClassExpression ] ')'
  487DataSomeValuesFrom := 'DataSomeValuesFrom' '(' DataPropertyExpression { DataPropertyExpression } DataRange ')'
  488DataAllValuesFrom := 'DataAllValuesFrom' '(' DataPropertyExpression { DataPropertyExpression } DataRange ')'
  489DataHasValue := 'DataHasValue' '(' DataPropertyExpression Literal ')'
  490DataMinCardinality := 'DataMinCardinality' '(' nonNegativeInteger DataPropertyExpression [ DataRange ] ')'
  491DataMaxCardinality := 'DataMaxCardinality' '(' nonNegativeInteger DataPropertyExpression [ DataRange ] ')'
  492DataExactCardinality := 'DataExactCardinality' '(' nonNegativeInteger DataPropertyExpression [ DataRange ] ')'
  493*/
  494
  495/* Funzioni che controllano IRI */
  496individual2manchester(PE, PEF):-
  497  iri(PE,PEF).
  498
  499propertyExpression2manchester(PE, PEF):-
  500  iri(PE,PEF).
  501
  502/* Per ogni IRI inserisco < > e lascio uno spazio per rendere piĆ¹ leggibile la stampa */
  503iri(IRI,IRIF) :- 
  504  atomic(IRI),
  505  (trill_2_manch_setting(convertion_mode(simple)) ->
  506    utility_translation:collapse_ns(IRI,IRIF,_,[no_base(_)]) ;
  507    atomic_list_concat([' <',IRI,'> '],IRIF)
  508  ).
  509
  510% objectIntersectionOf(+CE) is semidet
  511objectIntersectionOf(intersectionOf(CEs),ClassExpressionFL):-
  512   ClassExpressionF = 'and',
  513   findall(CEF,(member(CE,CEs),classExpression2manchester(CE,CEF)),L),
  514   appendManchester4(ClassExpressionF,L,ClassExpressionFL).
  515
  516% objectSomeValuesFrom(+R) is semidet
  517objectSomeValuesFrom(someValuesFrom(P,C),SVFFunc):-
  518  classExpression2manchester(C,CF),
  519  propertyExpression2manchester(P,PF),
  520  appendManchester4('some',[PF,CF], SVFFunc).
  521
  522% objectUnionOf(+CE) is semidet
  523objectUnionOf(unionOf(CEs),ClassExpressionFL):-
  524  ClassExpressionF = 'or',
  525  findall(CEF,(member(CE,CEs),classExpression2manchester(CE,CEF)),L),
  526  appendManchester4(ClassExpressionF,L,ClassExpressionFL).
  527
  528% objectComplementOf(+CE) is semidet
  529objectComplementOf(complementOf(CE), CEF):-
  530  classExpression2manchester(CE,CEs),
  531  appendManchester4('not', [CEs], CEF). 
  532
  533% objectOneOf(+CE) is semidet
  534objectOneOf(oneOf(List), CEFs) :-
  535  findall(CEF, (member(CE,List),classExpression2manchester(CE,CEF)), L),
  536  appendManchester5(L, CEFs). 
  537
  538% objectAllValuesFrom(+R) is semidet
  539objectAllValuesFrom(allValueFrom(P, C), AVFFunc):-
  540  classExpression2manchester(C, CF),
  541  propertyExpression2manchester(P, PF),
  542  appendManchester4('only',[PF,CF], AVFFunc).
  543
  544% objectHasValue(+R) is semidet
  545objectHasValue(hasValue(P,I), HVFunc):-
  546  propertyExpression2manchester(P, PF),
  547  individual2manchester(I, IF),
  548  appendManchester4('value', [PF, IF], HVFunc).
  549
  550% objectHasSelf(+R) is semidet
  551objectHasSelf(hasSelf(P), HVFunc):-
  552  propertyExpression2manchester(P, PF),
  553  appendManchester4(PF, 'Self', HVFunc).
  554
  555% objectMinCardinality(+CR) is semide
  556objectMinCardinality(minCardinality(C, P, E), OMiCFunc):-
  557  number(C),
  558  C>=0,
  559  propertyExpression2manchester(P, PF),
  560  classExpression2manchester(E, EF),
  561  appendManchester6('min',[C,PF,EF], OMiCFunc).
  562
  563objectMinCardinality(minCardinality(C, P), OMiCFunc):-
  564  number(C),
  565  C>=0,
  566  propertyExpression2manchester(P, PF),
  567  appendManchester4('min',[PF,C], OMiCFunc).
  568
  569% objectMaxCardinality(+CR) is semidet
  570objectMaxCardinality(maxCardinality(C, P, E), OMaCFunc):-
  571  number(C),
  572  C>=0,
  573  propertyExpression2manchester(P, PF),
  574  classExpression2manchester(E, EF),
  575  appendManchester6('max',[C,PF,EF], OMaCFunc).
  576
  577objectMaxCardinality(maxCardinality(C, P), OMaCFunc):-
  578  number(C),
  579  C>=0,
  580  propertyExpression2manchester(P, PF),
  581  appendManchester4('max',[PF,C], OMaCFunc).
  582
  583% objectExactCardinality(+CR) is semidet  
  584objectExactCardinality(exactCardinality(C, P, E), OECFunc):-
  585  number(C),
  586  C>=0,
  587  propertyExpression2manchester(P, PF),
  588  classExpression2manchester(E, EF),
  589  appendManchester6('exactly',[C,PF,EF], OECFunc).
  590
  591objectExactCardinality(exactCardinality(C, P), OECFunc):-
  592  number(C),
  593  C>=0,
  594  propertyExpression2manchester(P, PF),
  595  appendManchester4('exactly',[C,PF], OECFunc).
  596
  597% dataSomeValuesFrom(+DR) is semidet
  598dataSomeValuesFrom(someValuesFrom(DE), DataPropertyExpressionFL):-
  599  DataPropertyExpressionF= 'some',
  600  dataExpression2manchester(DE,DEF),
  601	% dataRange(DR) 
  602  appendManchester4(DataPropertyExpressionF, DEF, DataPropertyExpressionFL).
  603
  604% dataAllValuesFrom(+DR) is semidet
  605dataAllValuesFrom(allValuesFrom(DE), DataPropertyExpressionFL):-
  606  DataPropertyExpressionF= 'only',
  607  dataExpression2manchester(DE,DEF),
  608	% dataRange(DR)
  609  appendManchester4(DataPropertyExpressionF, DEF, DataPropertyExpressionFL).
  610
  611% dataHasValue(+DR) is semidet
  612dataHasValue(hasValue(P,I), DVFunc):-
  613  dataPropertyExpression2manchester(P, PF),
  614  literal2manchester(I, IF),
  615  appendManchester4('value', [PF, IF], DVFunc).
  616
  617% dataMinCardinality(+DR) is semidet
  618dataMinCardinality(minCardinality(C, P), DMiCFunc):- 
  619  number(C),
  620  C>=0,
  621  propertyExpression2manchester(P, PF),
  622  appendManchester4('min',[C,PF], DMiCFunc).
  623
  624% dataMaxCardinality(+DR) is semidet
  625dataMaxCardinality(maxCardinality(C, P), DMaCFunc):- 
  626  number(C),
  627  C>=0,
  628  propertyExpression2manchester(P, PF),
  629  appendManchester4('max',[C,PF], DMaCFunc).
  630
  631% dataExactCardinality(+DR) is semidet
  632dataExactCardinality(exactCardinality(C, P), DECFunc):-
  633  number(C),
  634  C>=0,
  635  propertyExpression2manchester(P, PF),
  636  appendManchester4('exactly',[C,PF], DECFunc).
  637
  638
  639/* Lists concatenation */
  640
  641/* Axiom */
  642appendManchester(Pred, Lista, Ris):-
  643  atomic_list_concat([Pred,': '|Lista], Ris).   
  644
  645/* Ontology and Declaration */
  646appendManchester1(Pred2, Lista2, Ris2):-
  647    atomic_list_concat([Pred2,': '|Lista2], Ris2).
  648
  649/* General concat */
  650appendManchester2(List, Ris):-
  651  divide_with_pred(' ',List,ListPred),
  652  atomic_list_concat(ListPred, Ris). 
  653
  654/* Declaration */
  655appendManchester3(Pred2, Lista2, Ris2):-
  656  atomic_list_concat([Pred2,'('|Lista2], Atom3), 
  657  atomic_concat(Atom3, ')', Ris2).
  658
  659/* List concat */
  660appendManchester4(Pred, List, Ris4):-
  661  atomic_list_concat([' ', Pred, ' '], PredSp),
  662  divide_with_pred(PredSp,List,ListPred),
  663  atomic_list_concat(ListPred,Ris4).
  664
  665divide_with_pred(Pred, [El1], [Pred, El1]):- !.
  666
  667divide_with_pred(Pred, El1, [Pred, El1]):- 
  668  atom(El1),!.
  669
  670divide_with_pred(Pred, [El1, El2], [El1, Pred, El2]):- !.
  671
  672divide_with_pred(Pred, [H| T], [H, Pred| T1]):- 
  673  divide_with_pred(Pred,T,T1).
  674
  675appendManchester5(Lista2, Ris2):-
  676  atomic_list_concat(['{'|Lista2], Atom3), 
  677  atomic_concat(Atom3, '}', Ris2).
  678
  679appendManchester6(Pred, [C,PF,EF], Ris2):-
  680  atomic_list_concat([' ', Pred, ' '], PredSp),
  681  atomic_list_concat([PF, PredSp, C, EF], Ris2).
  682
  683
  684/* File writing kb_func.owl */
  685
  686writefile:-
  687  
  688  /* File creation kb_funct.owl*/
  689  open('kb_funct.owl', write, Stream),
  690  nl(Stream),
  691
  692  /* Prefixes writing */
  693  kb_prefixes(Le),
  694  foreach(member(K=P,Le), 
  695    (
  696      write(Stream, 'Prefix: '), 
  697      write(Stream, K),
  698      write(Stream, ': '),
  699      write(Stream, P),
  700      write(Stream, '>)\n')
  701    )
  702  ),
  703  write(Stream,'\n'),
  704
  705  /* Ontology writing */
  706  findall(PO, (axiom(ontology(Oiri)),prolog2manchester(ontology(Oiri),PO)),Lo),
  707  foreach(member(Os, Lo), writeln(Stream, Os)), 
  708  write(Stream,'\n'),
  709
  710  /* Axiom writing */
  711  findall(OP,(axiom(Ax),Ax\=ontology(_),prolog2manchester(Ax,OP)),La),
  712  foreach(member(As,La), writeln(Stream,As)),
  713
  714  /* Closing parenthesis and ending file writing */
  715  write(Stream,'\n'),
  716  close(Stream).
 convert_explanations(++TRILLExplanations:list, -OWLManchesterExplanations:list) is det
The predicate converts the axioms contained in the list of explanations returned by TRILL into OWL Manchester sytntax. /
  724convert_explanations([],[]).
  725
  726convert_explanations([ExplTRILL|ExplsTRILL],[ExplFunct|ExplsFunct]):-
  727  convert_explanation(ExplTRILL,ExplFunct),
  728  convert_explanations(ExplsTRILL,ExplsFunct).
  729
  730convert_explanation([],[]).
  731
  732convert_explanation([TRILLAx|OtherTRILLAxs],[FunctAx|OtherFunctAxs]):-
  733  prolog2manchester(TRILLAx,FunctAx),
  734  convert_explanation(OtherTRILLAxs,OtherFunctAxs).
 convert_axiom(++TRILLAxiom:axiom, -OWLManchesterAxiom:axiom) is det
The predicate converts the axiom TRILLAxiom from TRILL format to OWL Manchester syntax. /
  741convert_axiom(TRILLAx,FunctAx):-
  742  prolog2manchester(TRILLAx,FunctAx)