1:- module(xdrs2xml,[drs2xml/2,
    2                    der2xml/3,
    3                    xdrs2xml/2]).    4
    5:- use_module(semlib(errors),[warning/2]).    6:- use_module(library(lists),[member/2,append/3,select/3]).    7:- use_module(boxer(betaConversionDRT),[betaConvert/2]).    8:- use_module(boxer(alphaConversionDRT),[alphaConvertDRS/2]).    9:- use_module(boxer(drs2fdrs),[instDrs/1]).   10
   11
   12/*========================================================================
   13   Converting DRSs to XML
   14========================================================================*/
   15
   16drs2xml(DRS,Stream):- drs2xml(DRS,Stream,1,[]).
   17
   18der2xml(Der,I,Stream):- 
   19   format(Stream,' <der id="~p">~n',[I]),
   20   deri2xml(Der,Stream,2),
   21   format(Stream,' </der>~n',[]).
   22
   23xdrs2xml(XDRS,Stream):-
   24   XDRS=xdrs(Tags,DRS),
   25   write(Stream,' <taggedtokens>'), nl(Stream),
   26   tokentags2xml(Tags,Stream),
   27   write(Stream,' </taggedtokens>'), nl(Stream),
   28   drs2xml(DRS,Stream,1,Tags).
   29
   30
   31/*========================================================================
   32   Converting CCG derivation to XML (with tab insertion)
   33========================================================================*/
   34
   35deri2xml(t(Cat,Token,Sem,Att,Index),Stream,Tab):- !,
   36   tab(Stream,Tab), format(Stream,'<lex id="~p">~n',[Index]),
   37   NewTab is Tab + 2,
   38   symbol(Token,NiceToken),
   39   tab(Stream,Tab), format(Stream,' <token>~p</token>~n',[NiceToken]), 
   40   tags2xml(Att,Stream,Tab),
   41   tab(Stream,Tab), format(Stream,' <cat>~n',[]),
   42   numbervars(Cat,23,_),
   43   cat2xml(Cat,Stream,NewTab),
   44   tab(Stream,Tab), format(Stream,' </cat>~n',[]),  
   45   tab(Stream,Tab), format(Stream,' <sem>~n',[]),  
   46   betaConvert(Sem,Red),
   47   \+ \+ (instDrs(Red),
   48          drs2xml(Red,Stream,NewTab,[])), 
   49   tab(Stream,Tab), format(Stream,' </sem>~n',[]),  
   50   tab(Stream,Tab), format(Stream,'</lex>~n',[]).
   51
   52deri2xml(Der,Stream,Tab):- 
   53   Der =.. [Rule,Cat,_,Sem,_,Tokens,Under], 
   54   member(Rule,[tc,ftr,btr]), !,
   55   NewTab is Tab + 1,
   56   NextTab is Tab + 1,
   57   tab(Stream,Tab), urule2xml(Stream,Rule),
   58   tab(Stream,Tab), format(Stream,' <cat>~n',[]),  
   59   numbervars(Cat,23,_),
   60   cat2xml(Cat,Stream,NewTab),
   61   tab(Stream,Tab), format(Stream,' </cat>~n',[]),  
   62   tab(Stream,Tab), format(Stream,' <sem>~n',[]),  
   63   betaConvert(Sem,Red),
   64   \+ \+ (instDrs(Red),
   65          drs2xml(Red,Stream,NewTab,[])),
   66   tab(Stream,Tab), format(Stream,' </sem>~n',[]),  
   67   deri2xml(Under,Stream,NewTab),
   68   tab(Stream,NewTab), format(Stream,'<tokens>~n',[]),  
   69   tokens2xml(Tokens,NextTab,Stream),
   70   tab(Stream,NewTab), format(Stream,'</tokens>~n',[]),  
   71   tab(Stream,Tab), format(Stream,'</unaryrule>~n',[]).
   72
   73deri2xml(Der,Stream,Tab):- 
   74   Der =.. [conj,Cat,_,Sem,_,Tokens,Left,Right], !,
   75   NewTab is Tab + 1,
   76   NextTab is Tab + 2,
   77   tab(Stream,Tab), brule2xml(Stream,conj),
   78   tab(Stream,NewTab), format(Stream,'<cat>~n',[]),  
   79   numbervars(Cat,23,_),
   80   cat2xml(Cat,Stream,NextTab),
   81   tab(Stream,NewTab), format(Stream,'</cat>~n',[]),  
   82   tab(Stream,NewTab), format(Stream,'<sem>~n',[]),  
   83   betaConvert(Sem,Red), 
   84   \+ \+ (instDrs(Red),
   85          drs2xml(Red,Stream,NewTab,[])),
   86   tab(Stream,NewTab), format(Stream,'</sem>~n',[]),  
   87   deri2xml(Left,Stream,NewTab),   
   88   deri2xml(Right,Stream,NewTab),
   89   tab(Stream,NewTab), format(Stream,'<tokens>~n',[]),  
   90   tokens2xml(Tokens,NextTab,Stream),
   91   tab(Stream,NewTab), format(Stream,'</tokens>~n',[]), 
   92   tab(Stream,Tab),  format(Stream,'</binaryrule>~n',[]).
   93
   94deri2xml(Der,Stream,Tab):- 
   95   Der =.. [Rule,Cat,Sem,_,Tokens,Left,Right], !,
   96   NewTab is Tab + 1,
   97   NextTab is Tab + 2,
   98   tab(Stream,Tab), brule2xml(Stream,Rule),
   99   tab(Stream,NewTab), format(Stream,'<cat>~n',[]),  
  100   numbervars(Cat,23,_),
  101   cat2xml(Cat,Stream,NextTab),
  102   tab(Stream,NewTab), format(Stream,'</cat>~n',[]),  
  103   tab(Stream,NewTab), format(Stream,'<sem>~n',[]),  
  104   betaConvert(Sem,Red1),
  105   alphaConvertDRS(Red1,Red), % needed for functions introduced by NN compounds...
  106   \+ \+ (instDrs(Red),
  107          drs2xml(Red,Stream,NewTab,[])),
  108   tab(Stream,NewTab), format(Stream,'</sem>~n',[]),  
  109   deri2xml(Left,Stream,NewTab),   
  110   deri2xml(Right,Stream,NewTab),
  111   tab(Stream,NewTab), format(Stream,'<tokens>~n',[]),  
  112   tokens2xml(Tokens,NextTab,Stream),
  113   tab(Stream,NewTab), format(Stream,'</tokens>~n',[]), 
  114   tab(Stream,Tab),  format(Stream,'</binaryrule>~n',[]).
  115
  116deri2xml(_,_,_).
  117
  118
  119/*========================================================================
  120   Producing CCG unary rules in XML
  121========================================================================*/
  122
  123urule2xml(Stream,ftr):- !,
  124   format(Stream,'<unaryrule type="ftr" description="Forward Type Raising">~n',[]).
  125
  126urule2xml(Stream,btr):- !,
  127   format(Stream,'<unaryrule type="btr" description="Backward Type Raising">~n',[]).
  128
  129urule2xml(Stream,tc):- !,
  130   format(Stream,'<unaryrule type="tc" description="Type Changing">~n',[]).
  131
  132urule2xml(Stream,Type):-
  133   format(Stream,'<unaryrule type="~p">~n',[Type]).
  134
  135
  136/*========================================================================
  137   Producing CCG binary rules in XML
  138========================================================================*/
  139
  140brule2xml(Stream,Type):- Type = fa, !,
  141   format(Stream,'<binaryrule type="~p" description="Forward Application">~n',[Type]).
  142
  143brule2xml(Stream,Type):- Type = ba, !,
  144   format(Stream,'<binaryrule type="~p" description="Backward Application">~n',[Type]).
  145
  146brule2xml(Stream,Type):- member(Type,[fc,gfc]), !,
  147   format(Stream,'<binaryrule type="~p" description="Forward Composition">~n',[Type]).
  148
  149brule2xml(Stream,Type):- member(Type,[bc,gbc]), !,
  150   format(Stream,'<binaryrule type="~p" description="Backward Composition">~n',[Type]).
  151
  152brule2xml(Stream,Type):- member(Type,[fxc,gfxc]), !,
  153   format(Stream,'<binaryrule type="~p" description="Forward Crossed Composition">~n',[Type]).
  154
  155brule2xml(Stream,Type):- member(Type,[bxc,gbxc]), !,
  156   format(Stream,'<binaryrule type="~p" description="Backward Crossed Composition">~n',[Type]).
  157
  158brule2xml(Stream,Type):- Type = fxs, !,
  159   format(Stream,'<binaryrule type="~p" description="Forward Crossed Substitution">~n',[Type]).
  160
  161brule2xml(Stream,Type):- Type = bxs, !,
  162   format(Stream,'<binaryrule type="~p" description="Backward Crossed Substitution">~n',[Type]).
  163
  164brule2xml(Stream,Type):- Type = fs, !,
  165   format(Stream,'<binaryrule type="~p" description="Forward Substitution">~n',[Type]).
  166
  167brule2xml(Stream,Type):- Type = bs, !,
  168   format(Stream,'<binaryrule type="~p" description="Backward Substitution">~n',[Type]).
  169
  170brule2xml(Stream,Type):- Type = conj, !,
  171   format(Stream,'<binaryrule type="conj" description="Conjunction">~n',[]).
  172
  173brule2xml(Stream,Type):-
  174   format(Stream,'<binaryrule type="~p">~n',[Type]).
  175
  176
  177/*========================================================================
  178   Converting CCG categories to XML (with tab insertion)
  179========================================================================*/
  180
  181cat2xml(Cat,Stream,Tab):- 
  182   var(Cat), !,
  183   tab(Stream,Tab), format(Stream,' <atomic>~p</atomic>~n',[Cat]).
  184
  185cat2xml('/'(L,R),Stream,Tab):- !,
  186   tab(Stream,Tab), format(Stream,'<forward>~n',[]),
  187   NewTab is Tab + 1,
  188   cat2xml(L,Stream,NewTab),
  189   cat2xml(R,Stream,NewTab),
  190   tab(Stream,Tab), format(Stream,'</forward>~n',[]).
  191
  192cat2xml('\\'(L,R),Stream,Tab):- !,
  193   tab(Stream,Tab), format(Stream,'<backward>~n',[]),
  194   NewTab is Tab + 1,
  195   cat2xml(L,Stream,NewTab),
  196   cat2xml(R,Stream,NewTab),
  197   tab(Stream,Tab), format(Stream,'</backward>~n',[]).
  198
  199cat2xml(Cat:_,Stream,Tab):-
  200   member(Cat,[n,conj]), !,  %%% Do not output features on N, conj
  201   cat2xml(Cat,Stream,Tab).
  202
  203cat2xml(Cat:Feature,Stream,Tab):-
  204   atom(Cat), !,       
  205   upcase_atom(Cat,Up),
  206   tab(Stream,Tab), format(Stream,' <atomic feature="',[]),
  207   write_term(Stream,Feature,[numbervars(true)]),
  208   format(Stream,'">~p</atomic>~n',[Up]).
  209
  210cat2xml(Cat,Stream,Tab):- 
  211   member(Cat:New,[conj:conj,comma:',',semi:';']), !,
  212   tab(Stream,Tab), format(Stream,' <atomic>~p</atomic>~n',[New]).
  213
  214cat2xml(Cat,Stream,Tab):- !,
  215   upcase_atom(Cat,Up),
  216   tab(Stream,Tab), format(Stream,' <atomic>~p</atomic>~n',[Up]).
  217
  218
  219/*========================================================================
  220   Guess Sentence ID (a bit of a hack, obviously!)
  221========================================================================*/
  222
  223getIDs(L:drs([_:I1:_|Dom],Conds),I3):- append(I1,I2,I3), getIDs(L:drs(Dom,Conds),I2).
  224getIDs(_:drs([],Conds),I):- getIDs(Conds,I).
  225
  226getIDs([],[]).
  227getIDs([_:I1:Cond|Conds],I3):- !, append(I1,I2,I3), getIDs([Cond|Conds],I2).
  228getIDs([prop(_,B)|Conds],I3):- !, getIDs(B,I1), append(I1,I2,I3), getIDs(Conds,I2).
  229getIDs([not(B)|Conds],I3):- !, getIDs(B,I1), append(I1,I2,I3), getIDs(Conds,I2).
  230getIDs([pos(B)|Conds],I3):- !, getIDs(B,I1), append(I1,I2,I3), getIDs(Conds,I2).
  231getIDs([nec(B)|Conds],I3):- !, getIDs(B,I1), append(I1,I2,I3), getIDs(Conds,I2).
  232getIDs([or(B1,B2)|Conds],I5):- !, getIDs(B1,I1), getIDs(B2,I2), append(I1,I2,I3), append(I3,I4,I5), getIDs(Conds,I4).
  233getIDs([imp(B1,B2)|Conds],I5):- !, getIDs(B1,I1), getIDs(B2,I2), append(I1,I2,I3), append(I3,I4,I5), getIDs(Conds,I4).
  234getIDs([duplex(_,B1,_,B2)|Conds],I5):- !, getIDs(B1,I1), getIDs(B2,I2), append(I1,I2,I3), append(I3,I4,I5), getIDs(Conds,I4).
  235getIDs([_|Conds],I):- !, getIDs(Conds,I).
  236getIDs(_,[]).
  237
  238
  239/*========================================================================
  240   Converting DRSs to XML (with tab insertion)
  241========================================================================*/
  242
  243drs2xml(Var,Stream,Tab,_):- 
  244   var(Var), !,
  245   tab(Stream,Tab), format(Stream,'<var>~p</var>~n',Var).
  246
  247drs2xml(Var,Stream,Tab,_):- 
  248   atom(Var), !,
  249   tab(Stream,Tab), format(Stream,'<var>~p</var>~n',Var).
  250
  251drs2xml(Var,Stream,Tab,_):- 
  252   Var =.. ['$VAR',_], !,
  253   tab(Stream,Tab), format(Stream,'<var>~p</var>~n',Var).
  254
  255drs2xml(drs(D,C),Stream,Tab,Words):- !,
  256   drs2xml(l:drs(D,C),Stream,Tab,Words).
  257
  258drs2xml(Label:drs(D,C),Stream,Tab,[]):- !,
  259   NewTab is Tab + 1,
  260   NextTab is Tab + 2,
  261   tab(Stream,Tab),    format(Stream,'<drs type="normal" label="~p">~n',[Label]),
  262   tab(Stream,NewTab), format(Stream,'<domain>~n',[]),
  263   dom2xml(D,Stream,NextTab),
  264   tab(Stream,NewTab), format(Stream,'</domain>~n',[]),
  265   tab(Stream,NewTab), format(Stream,'<conds>~n',[]),
  266   conds2xml(C,Stream,NextTab),
  267   tab(Stream,NewTab), format(Stream,'</conds>~n',[]),
  268   tab(Stream,Tab),    format(Stream,'</drs>~n',[]).
  269
  270drs2xml(Label:drs(D,C),Stream,Tab,Words):- !,
  271   NewTab is Tab + 1,
  272   NextTab is Tab + 2,
  273   tab(Stream,Tab),
  274   format(Stream,'<drs type="sentence" label="~p">~n',[Label]),
  275   tab(Stream,NewTab), format(Stream,'<tokens>~n',[]),
  276   getIDs(Label:drs(D,C),IDs), 
  277   sort(IDs,SortedIDs),
  278   tokens2xml(SortedIDs,Words,NextTab,Stream),
  279   tab(Stream,NewTab), format(Stream,'</tokens>~n',[]),
  280   tab(Stream,NewTab), format(Stream,'<domain>~n',[]),
  281   dom2xml(D,Stream,NextTab),
  282   tab(Stream,NewTab), format(Stream,'</domain>~n',[]),
  283   tab(Stream,NewTab), format(Stream,'<conds>~n',[]),
  284   conds2xml(C,Stream,NextTab),
  285   tab(Stream,NewTab), format(Stream,'</conds>~n',[]),
  286   tab(Stream,Tab),    format(Stream,'</drs>~n',[]).
  287
  288drs2xml(alfa(Type,B1,B2),Stream,Tab,_):- !,
  289   tab(Stream,Tab), format(Stream,'<alfa type="~p">~n',[Type]),
  290   NewTab is Tab + 1,
  291   drs2xml(B1,Stream,NewTab,[]),
  292   drs2xml(B2,Stream,NewTab,[]),
  293   tab(Stream,Tab), format(Stream,'</alfa>~n',[]).
  294
  295drs2xml(lam(X,B),Stream,Tab,_):- !,
  296   tab(Stream,Tab), format(Stream,'<lam>~n',[]),
  297   NewTab is Tab + 1,
  298   tab(Stream,Tab), format(Stream,' <var>~p</var>~n',X),
  299   drs2xml(B,Stream,NewTab,[]),
  300   tab(Stream,Tab), format(Stream,'</lam>~n',[]).
  301
  302drs2xml(app(B1,B2),Stream,Tab,_):- !,
  303   tab(Stream,Tab), format(Stream,'<app>~n',[]),
  304   NewTab is Tab + 1,
  305   drs2xml(B1,Stream,NewTab,[]),
  306   drs2xml(B2,Stream,NewTab,[]),
  307   tab(Stream,Tab), format(Stream,'</app>~n',[]).
  308
  309drs2xml(merge(B1,B2),Stream,Tab,_):- !,
  310   tab(Stream,Tab), format(Stream,'<merge>~n',[]),
  311   NewTab is Tab + 1,
  312   drs2xml(B1,Stream,NewTab,[]),
  313   drs2xml(B2,Stream,NewTab,[]),
  314   tab(Stream,Tab), format(Stream,'</merge>~n',[]).
  315
  316drs2xml(sdrs(Labs,Rels),Stream,Tab,Words):- !,
  317   NewTab is Tab + 1,
  318   NewerTab is NewTab + 1,
  319   tab(Stream,Tab), format(Stream,'<sdrs>~n',[]),
  320   tab(Stream,NewTab), format(Stream,'<constituents>~n',[]),
  321   sdrs2xml(Labs,Stream,NewerTab,Words,Rels),
  322   tab(Stream,NewTab), format(Stream,'</constituents>~n',[]),
  323   tab(Stream,NewTab), format(Stream,'<relations>~n',[]),
  324   relations2xml(Rels,Stream,NewerTab),
  325   tab(Stream,NewTab), format(Stream,'</relations>~n',[]),
  326   tab(Stream,Tab), format(Stream,'</sdrs>~n',[]).
  327
  328drs2xml(Error,_,_,_):- !,
  329   warning('cannot print DRS in XML: ~p',[Error]).
  330
  331
  332/*========================================================================
  333   Converting SDRS to XML
  334========================================================================*/
  335
  336sdrs2xml([],_,_,_,_):- !.
  337
  338sdrs2xml([lab(K,B)|L],Stream,Tab,Words,Rel):- !,
  339   label2xml(K,B,Stream,Tab,Words),
  340   sdrs2xml(L,Stream,Tab,Words,Rel).   
  341
  342sdrs2xml([sub(lab(K1,B1),lab(K2,B2))|L],Stream,Tab,Words,Rel):-
  343   tab(Stream,Tab), format(Stream,'<sub>~n',[]),
  344   label2xml(K1,B1,Stream,Tab,Words),
  345   label2xml(K2,B2,Stream,Tab,Words),
  346   tab(Stream,Tab), format(Stream,'</sub>~n',[]),
  347   sdrs2xml(L,Stream,Tab,Words,Rel).   
  348
  349
  350/*========================================================================
  351   Converting SDRS constituent to XML
  352========================================================================*/
  353
  354label2xml(K,B,Stream,Tab,Words):-
  355   tab(Stream,Tab), format(Stream,'<constituent label="~p">~n',[K]),
  356   NewTab is Tab + 1, 
  357   drs2xml(B,Stream,NewTab,Words),
  358   tab(Stream,Tab), format(Stream,'</constituent>~n',[]).
  359
  360
  361/*========================================================================
  362   Converting SDRS relations to XML
  363========================================================================*/
  364
  365relations2xml([],_,_).
  366
  367relations2xml([Index:rel(K1,K2,Rel)|L],Stream,Tab):-
  368   tab(Stream,Tab), format(Stream,'<drel arg1="~p" arg2="~p" sym="~p">~n',[K1,K2,Rel]),
  369   index2xml(Index,Stream,Tab),
  370   tab(Stream,Tab), format(Stream,'</drel>~n',[]),
  371   relations2xml(L,Stream,Tab).   
  372
  373
  374/*========================================================================
  375   Converting DRS-domains to XML (with tab insertion)
  376========================================================================*/
  377
  378dom2xml([],_,_).
  379
  380dom2xml([Label:Index:X|L],Stream,Tab):- !,
  381   tab(Stream,Tab),   
  382   format(Stream,'<dr label="~p" name="~p">~n',[Label,X]),
  383   index2xml(Index,Stream,Tab),
  384   tab(Stream,Tab),
  385   format(Stream,'</dr>~n',[]),
  386   dom2xml(L,Stream,Tab).
  387
  388dom2xml([Index:X|L],Stream,Tab):- !,
  389   dom2xml([l:Index:X|L],Stream,Tab).
  390
  391dom2xml([X|L],Stream,Tab):-
  392   warning('cannot print referent in XML: ~p',[X]),
  393   dom2xml(L,Stream,Tab).
  394
  395
  396
  397/*========================================================================
  398   Converting DRS-conditions to XML (with tab insertion)
  399========================================================================*/
  400
  401conds2xml([],_,_).
  402
  403conds2xml([Label:Index:Cond|L],Stream,Tab):-
  404   tab(Stream,Tab), format(Stream,'<cond label="~p">~n',[Label]),
  405   NewTab is Tab + 1,
  406   cond2xml(Index:Cond,Stream,NewTab), !,
  407   tab(Stream,Tab), format(Stream,'</cond>~n',[]),
  408   conds2xml(L,Stream,Tab).
  409
  410conds2xml([Index:Cond|L],Stream,Tab):- !,
  411   conds2xml([l:Index:Cond|L],Stream,Tab).
  412
  413conds2xml([X|L],Stream,Tab):-
  414   warning('cannot print condition in XML: ~p',[X]),
  415   format(Stream,'</cond>~n',[]),
  416   conds2xml(L,Stream,Tab).
  417
  418
  419/*========================================================================
  420   Converting DRS-condition to XML (with tab insertion)
  421========================================================================*/
  422
  423cond2xml(Index:not(B),Stream,Tab):- !,
  424   tab(Stream,Tab), format(Stream,'<not>~n',[]),
  425   index2xml(Index,Stream,Tab),
  426   NewTab is Tab + 1,
  427   drs2xml(B,Stream,NewTab,[]),
  428   tab(Stream,Tab), format(Stream,'</not>~n',[]).
  429
  430cond2xml(Index:nec(B),Stream,Tab):- !,
  431   tab(Stream,Tab), format(Stream,'<nec>~n',[]),
  432   index2xml(Index,Stream,Tab),
  433   NewTab is Tab + 1,
  434   drs2xml(B,Stream,NewTab,[]),
  435   tab(Stream,Tab), format(Stream,'</nec>~n',[]).
  436
  437cond2xml(Index:pos(B),Stream,Tab):- !,
  438   tab(Stream,Tab), format(Stream,'<pos>~n',[]),
  439   index2xml(Index,Stream,Tab),
  440   NewTab is Tab + 1,
  441   drs2xml(B,Stream,NewTab,[]),
  442   tab(Stream,Tab), format(Stream,'</pos>~n',[]).
  443
  444cond2xml(Index:prop(X,B),Stream,Tab):- !,
  445   tab(Stream,Tab), format(Stream,'<prop argument="~p">~n',[X]),
  446   index2xml(Index,Stream,Tab),
  447   NewTab is Tab + 1,
  448   drs2xml(B,Stream,NewTab,[]),
  449   tab(Stream,Tab), format(Stream,'</prop>~n',[]).
  450
  451cond2xml(Index:or(B1,B2),Stream,Tab):- !,
  452   tab(Stream,Tab), format(Stream,'<or>~n',[]),
  453   index2xml(Index,Stream,Tab),
  454   NewTab is Tab + 1,
  455   drs2xml(B1,Stream,NewTab,[]),
  456   drs2xml(B2,Stream,NewTab,[]),
  457   tab(Stream,Tab), format(Stream,'</or>~n',[]).
  458
  459cond2xml(Index:imp(B1,B2),Stream,Tab):- !,
  460   tab(Stream,Tab), format(Stream,'<imp>~n',[]),
  461   index2xml(Index,Stream,Tab),
  462   NewTab is Tab + 1,
  463   drs2xml(B1,Stream,NewTab,[]),
  464   drs2xml(B2,Stream,NewTab,[]),
  465   tab(Stream,Tab), format(Stream,'</imp>~n',[]).
  466
  467cond2xml(Index:duplex(Type,B1,Var,B2),Stream,Tab):- !,
  468   tab(Stream,Tab), format(Stream,'<duplex type="~p" var="~p">~n',[Type,Var]),
  469   index2xml(Index,Stream,Tab),
  470   NewTab is Tab + 1,
  471   drs2xml(B1,Stream,NewTab,[]),
  472   drs2xml(B2,Stream,NewTab,[]),
  473   tab(Stream,Tab), format(Stream,'</duplex>~n',[]).
  474
  475cond2xml(Index:pred(Arg,X,Type,Sense),Stream,Tab):- !,
  476   symbol(X,Y),
  477   tab(Stream,Tab), format(Stream,'<pred arg="~p" symbol="~w" type="~p" sense="~p">~n',[Arg,Y,Type,Sense]),
  478   index2xml(Index,Stream,Tab),
  479   tab(Stream,Tab), format(Stream,'</pred>~n',[]).
  480
  481cond2xml(Index:role(Arg2,Arg1,X,-1),Stream,Tab):- !,
  482   symbol(X,Y),
  483   tab(Stream,Tab), format(Stream,'<rel arg1="~p" arg2="~p" symbol="~w" sense="~p">~n',[Arg1,Arg2,Y,1]),
  484   index2xml(Index,Stream,Tab),
  485   tab(Stream,Tab),   
  486   format(Stream,'</rel>~n',[]).
  487
  488cond2xml(Index:role(Arg1,Arg2,X,1),Stream,Tab):- !,
  489   symbol(X,Y),
  490   tab(Stream,Tab), format(Stream,'<rel arg1="~p" arg2="~p" symbol="~w" sense="~p">~n',[Arg1,Arg2,Y,1]),
  491   index2xml(Index,Stream,Tab),
  492   tab(Stream,Tab),   
  493   format(Stream,'</rel>~n',[]).
  494
  495cond2xml(Index:rel(X,Y,Sym,0),Stream,Tab):-
  496   symbol(Sym,=), !,
  497   cond2xml(Index:eq(X,Y),Stream,Tab).
  498
  499cond2xml(Index:rel(Arg1,Arg2,X,Sense),Stream,Tab):- !,
  500   symbol(X,Y),
  501   tab(Stream,Tab), format(Stream,'<rel arg1="~p" arg2="~p" symbol="~w" sense="~p">~n',[Arg1,Arg2,Y,Sense]),
  502   index2xml(Index,Stream,Tab),
  503   tab(Stream,Tab),   
  504   format(Stream,'</rel>~n',[]).
  505
  506cond2xml(Index:named(Arg,X,Class,Type),Stream,Tab):- !,
  507   symbol(X,Y),
  508   tab(Stream,Tab), format(Stream,'<named arg="~p" symbol="~w" class="~p" type="~p">~n',[Arg,Y,Class,Type]),
  509   index2xml(Index,Stream,Tab),
  510   tab(Stream,Tab), format(Stream,'</named>~n',[]).
  511
  512cond2xml(Index:card(X,Y,Type),Stream,Tab):- !,
  513   tab(Stream,Tab), format(Stream,'<card arg="~p" value="~p" type="~p">~n',[X,Y,Type]),
  514   index2xml(Index,Stream,Tab),
  515   tab(Stream,Tab), format(Stream,'</card>~n',[]).
  516
  517cond2xml(Index:timex(X,Y),Stream,Tab):- !,
  518   tab(Stream,Tab), format(Stream,'<timex arg="~p">~n',[X]),
  519   index2xml(Index,Stream,Tab),
  520   timex2xml(Y,Stream,Tab),
  521   tab(Stream,Tab), format(Stream,'</timex>~n',[]).
  522
  523cond2xml(Index:eq(X,Y),Stream,Tab):- !,
  524   tab(Stream,Tab), format(Stream,'<eq arg1="~p" arg2="~p">~n',[X,Y]),
  525   index2xml(Index,Stream,Tab),
  526   tab(Stream,Tab), format(Stream,'</eq>~n',[]).
  527
  528
  529/*========================================================================
  530   Timex
  531========================================================================*/
  532
  533timex2xml(date(_:A,_:B,_:C),Stream,Tab):- !,
  534   tab(Stream,Tab), format(Stream,'<date>~w~w~w</date>~n',[A,B,C]).
  535
  536timex2xml(date(_:Z,_:A,_:B,_:C),Stream,Tab):- !,
  537   tab(Stream,Tab), format(Stream,'<date>~w~w~w~w</date>~n',[Z,A,B,C]).
  538
  539timex2xml(time(_:A,_:B,_:C),Stream,Tab):- !,
  540   tab(Stream,Tab), format(Stream,'<time>~w~w~w</time>~n',[A,B,C]).
  541
  542timex2xml(X,Stream,Tab):- !,
  543   tab(Stream,Tab), format(Stream,'<unknown>~p</unknown>~n',[X]).
  544
  545
  546/*========================================================================
  547   Tokens (already known)
  548========================================================================*/
  549
  550tokens2xml([],_,_).
  551
  552tokens2xml([Token|L],Tab,Stream):-
  553   symbol(Token,NiceToken),
  554   tab(Stream,Tab), format(Stream,'<token>~w</token>~n',[NiceToken]),
  555   tokens2xml(L,Tab,Stream).
  556
  557
  558/*========================================================================
  559   Tokens (from list of words)
  560========================================================================*/
  561
  562tokens2xml(I,[presup|Words],Tab,Stream):- !, tokens2xml(I,Words,Tab,Stream,presup).
  563tokens2xml(I,Words,Tab,Stream):- !, tokens2xml(I,Words,Tab,Stream,sentence).
  564
  565tokens2xml([],_,_,_,_).
  566
  567tokens2xml([Index],Words,Tab,Stream,_):-
  568   member(Index:[tok:Tok|_],Words), !,
  569   symbol(Tok,NiceToken),
  570   tab(Stream,Tab), format(Stream,'<token>~w</token>~n',[NiceToken]).
  571
  572tokens2xml([Index1,Index2|L],Words,Tab,Stream,Type):-
  573   Type = presup,
  574   member(Index1:[tok:Tok|_],Words), !,
  575   symbol(Tok,NiceToken),
  576   tab(Stream,Tab), format(Stream,'<token>~w</token>~n',[NiceToken]),
  577   ( Dif is Index2 - Index1, 
  578     Dif > 1, tab(Stream,Tab), format(Stream,'<token>|</token>~n',[])
  579   ; true ),
  580   tokens2xml([Index2|L],Words,Tab,Stream,Type).
  581
  582tokens2xml([Index1,Index2|L1],Words,Tab,Stream,Type):-
  583   Type = sentence,
  584   member(Index1:[tok:Tok|_],Words), !,
  585   symbol(Tok,NiceToken),
  586   tab(Stream,Tab), format(Stream,'<token>~w</token>~n',[NiceToken]),
  587   ( S is Index1-mod(Index1,1000), 
  588     S is Index2-mod(Index2,1000),
  589     Dif is Index2 - Index1, Dif > 1, !, Index is Index1 + 1,
  590     L2 = [Index,Index2|L1]
  591   ; L2 = [Index2|L1] ),
  592   tokens2xml(L2,Words,Tab,Stream,Type).
  593
  594tokens2xml([_|L],Words,Tab,Stream,Type):-
  595   tokens2xml(L,Words,Tab,Stream,Type).
  596
  597
  598/*========================================================================
  599   Check whether word is part of sentence
  600========================================================================*/
  601
  602wordInSentence(N1,N2):- 
  603   X is (N1-(mod(N1,1000)))/1000,
  604   X is (N2-(mod(N2,1000)))/1000.
  605
  606
  607/*========================================================================
  608   Token Tags
  609========================================================================*/
  610
  611tokentags2xml([],_).
  612
  613tokentags2xml([Index:Tags|L],Stream):-
  614   format(Stream,'  <tagtoken xml:id="i~p">~n',[Index]),
  615   format(Stream,'   <tags>~n',[]),
  616   tags2xml(Tags,Stream,4),
  617   format(Stream,'   </tags>~n',[]),
  618   format(Stream,'  </tagtoken>~n',[]),
  619   tokentags2xml(L,Stream).
  620
  621
  622/*========================================================================
  623   Producing tags in XML
  624========================================================================*/
  625
  626tags2xml([],_,_):- !.
  627
  628tags2xml(L1,Stream,Tab):- 
  629   select(sem:'EXS',L1,L2), 
  630   select(sem:'NOW',L2,L3), !,
  631   tags2xml([sem:'ENS'|L3],Stream,Tab).
  632
  633tags2xml(L1,Stream,Tab):- 
  634   select(sem:'EXS',L1,L2),
  635   select(sem:'PST',L2,L3), !,
  636   tags2xml([sem:'EPS'|L3],Stream,Tab).
  637
  638tags2xml(L1,Stream,Tab):- 
  639   select(sem:'EXS',L1,L2),
  640   select(sem:'FUT',L2,L3), !,
  641   tags2xml([sem:'EFS'|L3],Stream,Tab).
  642
  643tags2xml(L1,Stream,Tab):- 
  644   select(sem:'EXG',L1,L2),
  645   select(sem:'EXS',L2,L3), !,
  646   tags2xml([sem:'EXG'|L3],Stream,Tab).
  647
  648tags2xml(L1,Stream,Tab):- 
  649   select(sem:'EXT',L1,L2),
  650   select(sem:'EXS',L2,L3), !,
  651   tags2xml([sem:'EXT'|L3],Stream,Tab).
  652
  653tags2xml(L1,Stream,Tab):- 
  654   select(sem:Removed,L1,L2),
  655   select(sem:Sem,L2,L3), !,
  656   warning('double semantic tag detected: ~p',[Removed]),
  657   tags2xml([sem:Sem|L3],Stream,Tab).
  658
  659tags2xml([lemma:Lemma|L],Stream,Tab):- !,
  660   symbol(Lemma,NiceLemma),
  661   tab(Stream,Tab), format(Stream,' <tag type="lemma">~p</tag>~n',[NiceLemma]),  
  662   tags2xml(L,Stream,Tab).
  663
  664tags2xml([tok:Tok|L],Stream,Tab):- !,
  665   symbol(Tok,NiceTok),
  666   tab(Stream,Tab), format(Stream,' <tag type="tok">~p</tag>~n',[NiceTok]),  
  667   tags2xml(L,Stream,Tab).
  668
  669tags2xml([verbnet:Roles|L],Stream,Tab):- !,
  670   length(Roles,N),
  671   tab(Stream,Tab), format(Stream,' <tag type="verbnet" n="~p">~p</tag>~n',[N,Roles]),  
  672   tags2xml(L,Stream,Tab).
  673
  674tags2xml([Feature:Value|L],Stream,Tab):-   
  675   tab(Stream,Tab), format(Stream,' <tag type="~p">~p</tag>~n',[Feature,Value]),  
  676   tags2xml(L,Stream,Tab).
  677
  678
  679/*========================================================================
  680   Indexes
  681========================================================================*/
  682
  683index2xml(I,Stream,Tab):-
  684   tab(Stream,Tab), format(Stream,'<indexlist>~n',[]),
  685   index2xml2(I,Stream,Tab),
  686   tab(Stream,Tab), format(Stream,'</indexlist>~n',[]).
  687
  688index2xml2([],_,_):- !.
  689
  690index2xml2([X|L],Stream,Tab):-
  691   number(X), !,
  692   Pos is mod(X,1000),
  693   tab(Stream,Tab), format(Stream,'<index pos="~p">i~p</index>~n',[Pos,X]),
  694   index2xml2(L,Stream,Tab).
  695
  696index2xml2([_|L],Stream,Tab):-
  697   index2xml2(L,Stream,Tab).
  698
  699
  700/*========================================================================
  701   Deal with special symbols
  702========================================================================*/
  703
  704symbol(f(_,_,V1),V2):- !, V1 = V2.
  705
  706symbol(N1,N2):- number(N1), !, N2 = N2.
  707
  708symbol(S1,S2):- atom_codes(S1,C1), check(C1,C2), atom_codes(S2,C2).
  709
  710
  711/*========================================================================
  712   Check special characters
  713========================================================================*/
  714
  715check([],[]).
  716
  717%%% Special character &
  718%%%
  719check([38|L1],[38,97,109,112,59|L2]):- !,
  720   check(L1,L2).
  721
  722%%% Special character <
  723%%%
  724check([60|L1],[38,108,116,59|L2]):- !,
  725   check(L1,L2).
  726
  727%%% Special character >
  728%%%
  729check([62|L1],[38,103,116,59|L2]):- !,
  730   check(L1,L2).
  731
  732%%% Special character '
  733%%%
  734check([62|L1],[38,97,112,111,115,59|L2]):- !,
  735   check(L1,L2).
  736
  737%%% Special character "
  738%%%
  739check([34|L1],[38,113,117,111,116,59|L2]):- !,
  740   check(L1,L2).
  741
  742check([X|L1],[X|L2]):-
  743   check(L1,L2)