trill_2_funct

This module translates TRILL format into OWL functional syntax.

author
- Riccardo Zese, Matilda Moro
license
- Artistic License 2.0
   10:- module(trill_2_funct, [convert_explanations/2, convert_axiom/2]).   11
   12
   13% class(?IRI)
   14prolog2function(class(IRI), ClFunc):- 
   15  iri(IRI,IRIF),
   16  appendFunctional2('Class', [IRIF], ClFunc). 
   17
   18% datatype(?IRI)
   19prolog2function(datatype(IRI), DtFunc):- 
   20  iri(IRI,IRIF),
   21  appendFunctional2('Datatype', [IRIF], DtFunc).
   22
   23% objectProperty(?IRI)
   24prolog2function(objectProperty(IRI), OpFunc) :-
   25  iri(IRI,IRIF),
   26  appendFunctional2('ObjectProperty', [IRIF], OpFunc).
   27
   28% dataProperty(?IRI)
   29prolog2function(dataPropery(IRI), DPFunc):- 
   30  iri(IRI,IRIF),
   31  appendFunctional2('Dataproperty', [IRIF], DPFunc).
   32
   33% annotationProperty(?IRI)
   34prolog2function(annotationProperty(IRI), APFunc ):- 
   35  iri(IRI,IRIF),
   36  appendFunctional2('AnnotationProperty', [IRIF], APFunc).
   37
   38% namedIndividual(?IRI)
   39prolog2function(namedIndividual(IRI), NIFunc):- 
   40  iri(IRI,IRIF),
   41  appendFunctional2('NamedIndividual', [IRIF], NIFunc).
   42
   43% anonymousIndividual(?IRI)
   44prolog2function(anonymousIndividual(IRI), AIFunc):- 
   45  iri(IRI,IRIF),
   46  appendFunctional2('AnonymousIndividual', [IRIF], AIFunc).
   47
   48
   49/* ClassExpression e PropertyExpression */
   50
   51% subClassOf(?SubClass:ClassExpression, ?SuperClass:ClassExpression)
   52prolog2function(subClassOf(ClassExpression1, ClassExpression2), SCFunc):- %appendFunctional SubClassOf ClassExpressionFunctional1 ClassExpressionFunctional2 
   53  classExpression2function(ClassExpression1,ClassExpressionFunctional1),
   54  classExpression2function(ClassExpression2,ClassExpressionFunctional2), 
   55  appendFunctional('SubClassOf',[ClassExpressionFunctional1, ClassExpressionFunctional2],SCFunc).
   56
   57% equivalentClasses(?ClassExpressions:set(ClassExpression))
   58prolog2function(equivalentClasses(ListaClassExpression), ECFunc):-  %'EquivalentClasses(axiomAnnotations, ClassExpression, ClassExpression { ClassExpression } )'):-
   59  findall(CEF,(member(CE,ListaClassExpression),classExpression2function(CE,CEF)),L),
   60  appendFunctional('EquivalentClasses',L,ECFunc).
   61
   62% disjointClasses(?ClassExpressions:set(ClassExpression))
   63prolog2function(disjointClasses(ListaClassExpression), DCFunc):- %'DisjointClasses(axiomAnnotations, ClassExpression, ClassExpression { ClassExpression })'). 
   64  findall(CEF,(member(CE,ListaClassExpression),classExpression2function(CE,CEF)),L),
   65  appendFunctional('DisjointClasses',L,DCFunc).
   66
   67% disjointUnion(?ClassExpression, ?ClassExpressions:set(ClassExpression))
   68prolog2function(disjointUnion(IRI,ListaClassExpression), ECFunc):- %'DisjointUnion(axiomAnnotations, Class disjointClassExpressions)'% disjointClassExpressions := ClassExpression ClassExpression { ClassExpression })
   69  classExpression2function(IRI,ClassExpressionFunctional),
   70  findall(CEF,(member(CE,ListaClassExpression),classExpression2function(CE,CEF)),L),
   71  appendFunctional2('DisjointUnion',[ClassExpressionFunctional|L],ECFunc).
   72
   73% subPropertyOf(?Sub:PropertyExpression, ?Super:ObjectPropertyExpression)
   74prolog2function(subPropertyOf(PropertyExpression1, PropertyExpression2), SPFunc):- 
   75  propertyExpression2function(PropertyExpression1,PropertyExpressionFunctional1),
   76  propertyExpression2function(PropertyExpression2,PropertyExpressionFunctional2),
   77  appendFunctional('SubObjectPropertyOf',[PropertyExpressionFunctional1, PropertyExpressionFunctional2],SPFunc).
   78
   79% equivalentProperties(?PropertyExpressions:set(PropertyExpression))  
   80prolog2function(equivalentProperties(ListaPropertyExpression), EPFunc):- %'EquivalentObjectProperties(axiomAnnotations, ObjectPropertyExpression, ObjectPropertyExpression { ObjectPropertyExpression })').
   81  findall(PEF,(member(PE,ListaPropertyExpression), propertyExpression2function(PE,PEF)),A),
   82  appendFunctional('EquivalentObjectProperties', A, EPFunc).
   83
   84% disjointProperties(?PropertyExpressions:set(PropertyExpression))                
   85prolog2function(dijointProperties(ListaPropertyExpression), DPFunc):- %'DisjointObjectProperties(axiomAnnotations, ObjectPropertyExpression, ObjectPropertyExpression { ObjectPropertyExpression })').
   86  findall(PEF,(member(PE, ListaPropertyExpression), propertyExpression2function(PE,PEF)),A),
   87  appendFunctional('DisjointObjectProperties', A, DPFunc).
   88
   89% inverseProperties(?ObjectPropertyExpression1:ObjectPropertyExpression, ?ObjectPropertyExpression2:ObjectPropertyExpression)
   90prolog2function(inverseProperties(ObjectPropertyExpression1, ObjectPropertyExpression2), IOPFunc):- %'InverseObjectProperties(axiomAnnotations, ObjectPropertyExpression, ObjectPropertyExpression)'). 
   91  propertyExpression2function(ObjectPropertyExpression1,ObjectPropertyExpressionFunctional1),
   92  propertyExpression2function(ObjectPropertyExpression2,ObjectPropertyExpressionFunctional2), %appendFunctional SubClassOf ClassExpressionFunctional1 ClassExpressionFunctional2
   93  appendFunctional('InverseObjectProperties',[ObjectPropertyExpressionFunctional1, ObjectPropertyExpressionFunctional2],IOPFunc).
   94
   95% propertyDomain(?PropertyExpression, ?CE)
   96prolog2function(propertyDomain(PropertyExpression, ClassExpression), OPDFunc):- %'ObjectPropertyDomain(axiomAnnotations, ObjectPropertyExpression, ClassExpression)').
   97  propertyExpression2function(PropertyExpression,PropertyExpressionF),
   98  classExpression2function(ClassExpression,ClassExpressionF),
   99  appendFunctional('ObjectPropertyDomain',[PropertyExpressionF,ClassExpressionF],OPDFunc).
  100
  101% propertyRange(?PropertyExpression, ?ClassExpression)
  102prolog2function(propertyRange(PropertyExpression, ClassExpression), OPRFunc) :- %'ObjectPropertyRange(axiomAnnotations, ObjectPropertyExpression, ClassExpression)').
  103  propertyExpression2function(PropertyExpression,PropertyExpressionF),
  104  classExpression2function(ClassExpression,ClassExpressionF),
  105  appendFunctional('ObjectPropertyRange',[PropertyExpressionF,ClassExpressionF],OPRFunc).
  106
  107% functionalProperty(?PropertyExpression)
  108prolog2function(functionalProperty(PropertyExpression),FOPFunc) :- %'FunctionalObjectProperty(axiomAnnotations, ObjectPropertyExpression)'). %?
  109  propertyExpression2function(PropertyExpression,IRI),
  110  appendFunctional('FunctionalObjectProperty',[IRI] ,FOPFunc).
  111
  112% inverseFunctionalProperty(?ObjectPropertyExpression)
  113prolog2function(inverseFunctionalProperty(PropertyExpression), IFPFunc):- %'InverseFunctionalObjectProperty(axiomAnnotations, ObjectPropertyExpression').
  114  propertyExpression2function(PropertyExpression,IRI),
  115  appendFunctional('InverseFunctionalObjectProperty',[IRI] ,IFPFunc).
  116
  117% reflexiveProperty(?ObjectPropertyExpression)
  118prolog2function(reflexiveProperty(PropertyExpression), RPFunc) :- % ReflexiveObjectProperty(axiomAnnotations, ObjectPropertyExpression)'). 
  119  propertyExpression2function(PropertyExpression,IRI),
  120  appendFunctional('ReflexiveObjectProperty',[IRI] ,RPFunc).
  121
  122% irreflexiveProperty(?ObjectPropertyExpression)
  123prolog2function(irreflexiveProperty(PropertyExpression), IOPFunc):- %'IrreflexiveObjectProperty(axiomAnnotations, ObjectPropertyExpression)').  
  124  propertyExpression2function(PropertyExpression,IRI),
  125  appendFunctional('IrreflexiveObjectProperty', [IRI] ,IOPFunc).             
  126
  127% symmetricProperty(?ObjectPropertyExpression)
  128prolog2function(symmetricProperty(PropertyExpression), SOPFunc) :- %'SymmetricObjectProperty(axiomAnnotations, ObjectPropertyExpression)').              
  129  propertyExpression2function(PropertyExpression,IRI),
  130  appendFunctional('SymmetricObjectProperty', [IRI] ,SOPFunc).             
  131
  132% asymmetricProperty(?ObjectPropertyExpression)
  133prolog2function(asymmetricProperty(PropertyExpression), AOPFunc):- %'AsymmetricObjectProperty(axiomAnnotations, ObjectPropertyExpression)').             
  134  propertyExpression2function(PropertyExpression,IRI),
  135  appendFunctional('AsymmetricObjectProperty', [IRI] ,AOPFunc).             
  136
  137% transitiveProperty(?ObjectPropertyExpression)
  138prolog2function(transitiveProperty(PropertyExpression), TOPFunc):- %'TransitiveObjectProperty(axiomAnnotations, ObjectPropertyExpression)').
  139  propertyExpression2function(PropertyExpression,IRI),
  140  appendFunctional('TransitiveObjectProperty', [IRI] ,TOPFunc).             
  141
  142% hasKey(?ClassExpression,?PropertyExpression)
  143prolog2function(hasKey(ClassExpression,PropertyExpression), HKFunc):- %'HasKey(axiomAnnotations ClassExpression({ ObjectPropertyExpression }) ({ DataPropertyExpression }))'). 
  144  classExpression2function(ClassExpression,ClassExpressionF),
  145  propertyExpression2function(PropertyExpression,PropertyExpressionF),
  146  appendFunctional('HasKey',[ClassExpressionF,PropertyExpressionF],HKFunc).
  147
  148
  149/* Individual */
  150
  151% sameIndividual(?Individuals:set(Individual))
  152prolog2function(sameIndividual(ListIndividual), SIFunc) :- %'SameIndividual(axiomAnnotations, Individual Individual { Individual })').
  153  findall(IEF,(member(IE, ListIndividual), individual2function(IE,IEF)),A),
  154  appendFunctional('SameIndividual', A, SIFunc).
  155
  156% differentIndividuals(?Individuals:set(Individual))               
  157prolog2function(differentIndividual(ListIndividual), DIFunc ) :- %'DifferentIndividuals(axiomAnnotations, Individual Individual { Individual })').
  158  findall(IEF,(member(IE, ListIndividual), individual2function(IE,IEF)),A),
  159  appendFunctional('DifferentIndividual', A, DIFunc).
  160
  161
  162/* Assertion */
  163
  164% classAssertion(?ClassExpression, ?Individual)               
  165prolog2function(classAssertion(ClassExpression, IndividualExpression), CAFunc) :- %'ClassAssertion(axiomAnnotations, ClassExpression Individual)').
  166  classExpression2function(ClassExpression,ClassExpressionF),
  167  individual2function(IndividualExpression,IndividualExpressionF),
  168  appendFunctional('ClassAssertion',[ClassExpressionF,IndividualExpressionF],CAFunc).
  169
  170% propertyAssertion(?PropertyExpression, ?SourceIndividual:Individual, ?TargetIndividual:Individual)               
  171prolog2function(propertyAssertion(PropertyExpression, IndividualExpression1, IndividualExpression2), OPAFunc ):- %'ObjectPropertyAssertion( axiomAnnotations, ObjectPropertyExpression, sourceIndividual, targetIndividual)'). 
  172  propertyExpression2function(PropertyExpression,PropertyExpressionF),
  173  individual2function(IndividualExpression1, IndividualExpression1F),
  174  individual2function(IndividualExpression2, IndividualExpression2F),
  175  appendFunctional('ObjectPropertyAssertion', [PropertyExpressionF, IndividualExpression1F, IndividualExpression2F], OPAFunc).
  176
  177% negativePropertyAssertion(?PropertyExpression, ?SourceIndividual:Individual, ?TargetIndividual:Individual)
  178prolog2function(negativePropertyAssertion(PropertyExpression, IndividualExpression1, IndividualExpression2), NOPAFunc ):- %'NegativeObjectPropertyAssertion(axiomAnnotations, ObjectPropertyExpression, sourceIndividual, targetIndividual)'). 
  179  propertyExpression2function(PropertyExpression,PropertyExpressionF),
  180  individual2function(IndividualExpression1, IndividualExpression1F),
  181  individual2function(IndividualExpression2, IndividualExpression2F),
  182  appendFunctional('ObjectPropertyAssertion', [PropertyExpressionF, IndividualExpression1F, IndividualExpression2F], NOPAFunc).
  183
  184
  185/* Annotation */
  186
  187% annotationAssertion(?AnnotationProperty, ?AnnotationSubject, ?AnnotationValue)
  188prolog2function(annotationAssertion(AnnotationProperty, AnnotationSubject, AnnotationValue),AAFunc):- %'AnnotationAssertion(axiomAnnotations, AnnotationProperty, AnnotationSubject AnnotationValue)'.
  189  propertyExpression2function(AnnotationProperty, AnnotationPropertyF),
  190  propertyExpression2function(AnnotationSubject, AnnotationSubjectF),
  191  (
  192        % condition 
  193        iri(AnnotationValue,AnnotationValueF)
  194    ->
  195        % true 
  196        appendFunctional('AnnotationAssertion', [AnnotationPropertyF,AnnotationSubjectF,AnnotationValueF], AAFunc)
  197    ;
  198        % false 
  199        (literal2function(AnnotationValue, AnnotationValueF),
  200        appendFunctional2('AnnotationAssertion', [AnnotationPropertyF,AnnotationSubjectF,AnnotationValueF], AAFunc))
  201  ).
  202
  203% annotation(:IRI,?AnnotationProperty,?AnnotationValue)             
  204prolog2function(annotation(AnnotationProperty, AnnotationProperty, AnnotationValue), AFunc):-%(iri,annotationProperty,annotationValue),'Annotation(annotationAnnotations, AnnotationProperty, AnnotationValue)'
  205  propertyExpression2function(AnnotationProperty, AnnotationPropertyF),
  206  (
  207        % condition 
  208        iri(AnnotationValue,AnnotationValueF)
  209    ->
  210        % true 
  211        appendFunctional('AnnotationAssertion', [AnnotationPropertyF,AnnotationPropertyF,AnnotationValueF], AFunc)
  212    ;
  213        % false 
  214        literal2function(AnnotationValue, AnnotationValueF),
  215        appendFunctional2('AnnotationAssertion', [AnnotationPropertyF,AnnotationPropertyF,AnnotationValueF], AFunc)
  216  ).
  217
  218
  219/* Ontology */
  220
  221% ontology(?IRI)
  222prolog2function(ontology(IRI), OIFunc) :- 
  223  appendFunctional1('Ontology', [IRI], OIFunc).
  224
  225% ontologyImport(?Ontology, ?IRI)
  226prolog2function(ontologyImport(ontology(IRI)), OIMFunc):- 
  227  appendFunctional1('OntologyImport', [IRI], OIMFunc).
  228
  229% ontologyVersionInfo(?Ontology, ?IRI)
  230prolog2function(ontologyVersionInfo(ontology(IRI), OVFunc)):-
  231  appendFunctional1('OntologyVersionInfo', [IRI], OVFunc).
  232
  233
  234/*Class expression*/
  235
  236classExpression2function(CE,CEF):- 
  237  (iri(CE,CEF); 
  238  objectIntersectionOf(CE,CEF);
  239  objectSomeValuesFrom(CE,CEF); 
  240  objectUnionOf(CE, CEF);
  241  objectComplementOf(CE,CEF); 
  242  objectOneOf(CE,CEF);
  243  objectAllValuesFrom(CE,CEF); 
  244  objectHasValue(CE,CEF); 
  245  objectHasSelf(CE,CEF) ;
  246  objectMinCardinality(CE,CEF); 
  247  objectMaxCardinality(CE,CEF); 
  248  objectExactCardinality(CE,CEF); 
  249  dataSomeValuesFrom(CE,CEF);
  250  dataAllValuesFrom(CE,CEF); 
  251  dataHasValue(CE,CEF);
  252  dataMinCardinality(CE,CEF); 
  253  dataMaxCardinality(CE,CEF); 
  254  dataExactCardinality(CE,CEF)), 
  255  !.
  256
  257/*
  258ObjectIntersectionOf := 'ObjectIntersectionOf' '(' ClassExpression ClassExpression { ClassExpression } ')'
  259ObjectUnionOf := 'ObjectUnionOf' '(' ClassExpression ClassExpression { ClassExpression } ')'
  260ObjectComplementOf := 'ObjectComplementOf' '(' ClassExpression ')'
  261ObjectOneOf := 'ObjectOneOf' '(' Individual { Individual }')'
  262ObjectSomeValuesFrom := 'ObjectSomeValuesFrom' '(' ObjectPropertyExpression ClassExpression ')'
  263ObjectAllValuesFrom := 'ObjectAllValuesFrom' '(' ObjectPropertyExpression ClassExpression ')'
  264ObjectHasValue := 'ObjectHasValue' '(' ObjectPropertyExpression Individual ')'
  265ObjectHasSelf := 'ObjectHasSelf' '(' ObjectPropertyExpression ')'
  266ObjectMinCardinality := 'ObjectMinCardinality' '(' nonNegativeInteger ObjectPropertyExpression [ ClassExpression ] ')'
  267ObjectMaxCardinality := 'ObjectMaxCardinality' '(' nonNegativeInteger ObjectPropertyExpression [ ClassExpression ] ')'
  268ObjectExactCardinality := 'ObjectExactCardinality' '(' nonNegativeInteger ObjectPropertyExpression [ ClassExpression ] ')'
  269DataSomeValuesFrom := 'DataSomeValuesFrom' '(' DataPropertyExpression { DataPropertyExpression } DataRange ')'
  270DataAllValuesFrom := 'DataAllValuesFrom' '(' DataPropertyExpression { DataPropertyExpression } DataRange ')'
  271DataHasValue := 'DataHasValue' '(' DataPropertyExpression Literal ')'
  272DataMinCardinality := 'DataMinCardinality' '(' nonNegativeInteger DataPropertyExpression [ DataRange ] ')'
  273DataMaxCardinality := 'DataMaxCardinality' '(' nonNegativeInteger DataPropertyExpression [ DataRange ] ')'
  274DataExactCardinality := 'DataExactCardinality' '(' nonNegativeInteger DataPropertyExpression [ DataRange ] ')'
  275*/
  276
  277/* Funzioni che controllano IRI */
  278individual2function(PE, PEF):-
  279  iri(PE,PEF).
  280
  281propertyExpression2function(PE, PEF):-
  282  iri(PE,PEF).
  283
  284/* Per ogni IRI inserisco < > e lascio uno spazio per rendere piĆ¹ leggibile la stampa */
  285iri(IRI,IRIF) :- 
  286  atomic(IRI),
  287  atomic_list_concat(['<',IRI,'>'],IRIL),
  288  atomic_list_concat([IRIL,' '],IRIF).
  289
  290% objectIntersectionOf(+CE) is semidet
  291objectIntersectionOf(intersectionOf(CEs),ClassExpressionFL):-
  292   ClassExpressionF = 'ObjectIntersectionOf',
  293   findall(CEF,(member(CE,CEs),classExpression2function(CE,CEF)),L),
  294   appendFunctional(ClassExpressionF,L,ClassExpressionFL).
  295
  296% objectSomeValuesFrom(+R) is semidet
  297objectSomeValuesFrom(someValuesFrom(P,C),SVFFunc):-
  298  classExpression2function(C,CF),
  299  propertyExpression2function(P,PF),
  300  appendFunctional('ObjectSomeValuesFrom',[CF,PF], SVFFunc).
  301
  302% objectUnionOf(+CE) is semidet
  303objectUnionOf(unionOf(CEs),ClassExpressionFL):-
  304  ClassExpressionF = 'ObjectUnionOf',
  305  findall(CEF,(member(CE,CEs),classExpression2function(CE,CEF)),L),
  306  appendFunctional(ClassExpressionF,L,ClassExpressionFL).
  307
  308% objectComplementOf(+CE) is semidet
  309objectComplementOf(complementOf(CE), CEF):-
  310  classExpression2function(CE,CEs),
  311  appendFunctional('ObjectComplementOf', CEs, CEF). 
  312
  313% objectOneOf(+CE) is semidet
  314objectOneOf(oneOf(List), CEFs) :-
  315  findall(CEF, (member(CE,List),classExpression2function(CE,CEF)), L),
  316    appendFunctional('ObjectOneOf', L, CEFs). 
  317
  318% objectAllValuesFrom(+R) is semidet
  319objectAllValuesFrom(allValueFrom(P, C), AVFFunc):-
  320  classExpression2function(C, CF),
  321  propertyExpression2function(P, PF),
  322  appendFunctional('ObjectAllValuesFrom',[PF,CF], AVFFunc).
  323
  324% objectHasValue(+R) is semidet
  325objectHasValue(hasValue(P,I), HVFunc):-
  326  propertyExpression2function(P, PF),
  327  individual2function(I, IF),
  328  appendFunctional('ObjectHasValue', [PF, IF], HVFunc).
  329
  330% objectHasSelf(+R) is semidet
  331objectHasSelf(hasSelf(P), HVFunc):-
  332  propertyExpression2function(P, PF),
  333  appendFunctional('ObjectHasSelf', PF, HVFunc).
  334
  335% objectMinCardinality(+CR) is semide
  336objectMinCardinality(minCardinality(C, P, E), OMiCFunc):-
  337  number(C),
  338  C>=0,
  339  propertyExpression2function(P, PF),
  340  classExpression2function(E, EF),
  341  appendFunctional('ObjectMinCardinality',[C,PF,EF], OMiCFunc).
  342objectMinCardinality(minCardinality(C, P), OMiCFunc):-
  343  number(C),
  344  C>=0,
  345  propertyExpression2function(P, PF),
  346  appendFunctional('ObjectMinCardinality',[C,PF], OMiCFunc).
  347
  348% objectMaxCardinality(+CR) is semidet
  349objectMaxCardinality(maxCardinality(C, P, E), OMaCFunc):-
  350  number(C),
  351  C>=0,
  352  propertyExpression2function(P, PF),
  353  classExpression2function(E, EF),
  354  appendFunctional('ObjectMaxCardinality',[C,PF,EF], OMaCFunc).
  355objectMaxCardinality(maxCardinality(C, P), OMaCFunc):-
  356  number(C),
  357  C>=0,
  358  propertyExpression2function(P, PF),
  359  appendFunctional('ObjectMaxCardinality',[C,PF], OMaCFunc).
  360
  361% objectExactCardinality(+CR) is semidet  
  362objectExactCardinality(exactCardinality(C, P, E), OECFunc):-
  363  number(C),
  364  C>=0,
  365  propertyExpression2function(P, PF),
  366  classExpression2function(E, EF),
  367  appendFunctional('ObjectExactCardinality',[C,PF,EF], OECFunc).
  368objectExactCardinality(exactCardinality(C, P), OECFunc):-
  369  number(C),
  370  C>=0,
  371  propertyExpression2function(P, PF),
  372  appendFunctional('ObjectExactCardinality',[C,PF], OECFunc).
  373
  374% dataSomeValuesFrom(+DR) is semidet
  375dataSomeValuesFrom(someValuesFrom(DE), DataPropertyExpressionFL):-
  376  DataPropertyExpressionF= 'DataSomeValuesFrom',
  377  dataExpression2function(DE,DEF),
  378	% dataRange(DR) 
  379  appendFunctional(DataPropertyExpressionF, DEF, DataPropertyExpressionFL).
  380
  381% dataAllValuesFrom(+DR) is semidet
  382dataAllValuesFrom(allValuesFrom(DE), DataPropertyExpressionFL):-
  383  DataPropertyExpressionF= 'AllSomeValuesFrom',
  384  dataExpression2function(DE,DEF),
  385	% dataRange(DR)
  386  appendFunctional(DataPropertyExpressionF, DEF, DataPropertyExpressionFL).
  387
  388% dataHasValue(+DR) is semidet
  389dataHasValue(hasValue(P,I), DVFunc):-
  390  dataPropertyExpression2function(P, PF),
  391  literal2function(I, IF),
  392  appendFunctional('DataHasValue', [PF, IF], DVFunc).
  393
  394% dataMinCardinality(+DR) is semidet
  395dataMinCardinality(minCardinality(C, P), DMiCFunc):- 
  396  number(C),
  397  C>=0,
  398  propertyExpression2function(P, PF),
  399  appendFunctional('DataMinCardinality',[C,PF], DMiCFunc).
  400
  401% dataMaxCardinality(+DR) is semidet
  402dataMaxCardinality(maxCardinality(C, P), DMaCFunc):- 
  403  number(C),
  404  C>=0,
  405  propertyExpression2function(P, PF),
  406  appendFunctional('DataMaxCardinality',[C,PF], DMaCFunc).
  407
  408% dataExactCardinality(+DR) is semidet
  409dataExactCardinality(exactCardinality(C, P), DECFunc):-
  410  number(C),
  411  C>=0,
  412  propertyExpression2function(P, PF),
  413  appendFunctional('DataExactCardinality',[C,PF], DECFunc).
  414
  415
  416/* Lists concatenation */
  417
  418/* Axiom */
  419appendFunctional(Pred, Lista, Ris):-
  420  atomic_list_concat([Pred,'('|Lista], Atom), 
  421  atomic_concat(Atom, ')', Ris).   
  422
  423/* Ontology */
  424appendFunctional1(Pred1, Lista1, Ris1):-
  425  atomic_list_concat([Pred1,'(<'|Lista1], Atom1), 
  426  atomic_concat(Atom1, '>', Ris1).
  427
  428/* Declaration */
  429appendFunctional2(Pred2, Lista2, Ris2):-
  430    atomic_concat('Declaration(',Pred2, Atom2),
  431    atomic_list_concat([Atom2,'('|Lista2], Atom3), 
  432    atomic_concat(Atom3, '))', Ris2).
  433
  434
  435/* File writing kb_func.owl */
  436
  437writefile:-
  438  
  439  /* File creation kb_funct.owl*/
  440  open('kb_funct.owl', write, Stream),
  441  nl(Stream),
  442
  443  /* Prefixes writing */
  444  kb_prefixes(Le),
  445  foreach(member(K=P,Le), 
  446    (
  447      write(Stream, 'Prefix('), 
  448      write(Stream, K),
  449      write(Stream, ':=<'),
  450      write(Stream, P),
  451      write(Stream, '>)\n')
  452    )
  453  ),
  454  write(Stream,'\n'),
  455
  456  /* Ontology writing */
  457  findall(PO, (axiom(ontology(Oiri)),prolog2function(ontology(Oiri),PO)),Lo),
  458  foreach(member(Os, Lo), writeln(Stream, Os)), 
  459  write(Stream,'\n'),
  460
  461  /* Axiom writing */
  462  findall(OP,(axiom(Ax),Ax\=ontology(_),prolog2function(Ax,OP)),La),
  463  foreach(member(As,La), writeln(Stream,As)),
  464
  465  /* Closing parenthesis and ending file writing */
  466  write(Stream,')'), 
  467  write(Stream,'\n'),
  468  close(Stream).
 convert_explanations(++TRILLExplanations:list, -OWLFunctExplanations:list) is det
The predicate converts the axioms contained in the list of explanations returned by TRILL into OWL Functional sytntax. /
  476convert_explanations([],[]).
  477
  478convert_explanations([ExplTRILL|ExplsTRILL],[ExplFunct|ExplsFunct]):-
  479  convert_explanation(ExplTRILL,ExplFunct),
  480  convert_explanations(ExplsTRILL,ExplsFunct).
  481
  482convert_explanation([],[]).
  483
  484convert_explanation([TRILLAx|OtherTRILLAxs],[FunctAx|OtherFunctAxs]):-
  485  prolog2function(TRILLAx,FunctAx),
  486  convert_explanation(OtherTRILLAxs,OtherFunctAxs).
 convert_axiom(++TRILLAxiom:axiom, -OWLFunctAxiom:axiom) is det
The predicate converts the axiom TRILLAxiom from TRILL format to OWL Functional syntax. /
  493convert_axiom(TRILLAx,FunctAx):-
  494  prolog2function(TRILLAx,FunctAx)