2:- module(drs2tacitus,[drs2tac/4,printTAC/2,label/4]).    3
    4:- use_module(library(lists),[select/3,member/2]).    5:- use_module(semlib(errors),[warning/2]).    6:- use_module(semlib(options),[option/2]).    7
    8
    9/* ========================================================================
   10   Main Predicate
   11======================================================================== */
   12
   13drs2tac(DRS,Tags,N,TAC):- 
   14   drs2tac(DRS,Tags,[],TAC0,N-_,_),
   15   replace(TAC0,TAC).
   16
   17
   18/* ========================================================================
   19   Replacing equality statements
   20======================================================================== */
   21
   22replace(TAC1,TAC4):-
   23   select(replace(Old,New),TAC1,TAC2), !,
   24   replace(TAC2,Old,New,TAC3),
   25   replace(TAC3,TAC4).
   26
   27replace(TAC,TAC).
   28
   29replace(Atom,_,_,Atom):- atomic(Atom), !.
   30
   31replace([],_,_,[]):- !.
   32
   33replace([Var|L1],Old,New,[Var|L2]):- 
   34   var(Var), !,
   35   replace(L1,Old,New,L2).
   36
   37replace([Old|L1],Old,New,[New|L2]):- !,
   38   replace(L1,Old,New,L2).
   39
   40replace([Term1|L1],Old,New,[Term2|L2]):- 
   41   Term1 =.. [F|Args1], !,
   42   replace(Args1,Old,New,Args2),
   43   Term2 =.. [F|Args2],
   44   replace(L1,Old,New,L2).
   45
   46
   47/* ========================================================================
   48   Label
   49======================================================================== */
   50
   51label(X,Label,Var,Y):-
   52   var(Var), number(X),
   53   atom_codes(Label,[Code]), !,
   54   number_codes(X,Codes),
   55   atom_codes(Var,[Code|Codes]),
   56   Y is X + 1.
   57
   58label(X,_,_,X).
   59
   60
   61/* ========================================================================
   62   Translate DRSs into TACITUS formulas 
   63======================================================================== */
   64
   65drs2tac(alfa(_,B1,B2),P,T1,T2,N,H):- !, 
   66   drs2tac(merge(B1,B2),P,T1,T2,N,H).
   67
   68drs2tac(drs(_,Conds),P,T1,T2,N,H):- !, 
   69   conds2tac(Conds,P,T1,T2,N,H).
   70
   71drs2tac(merge(B1,B2),P,T1,T3,N1-N3,H2):- !, 
   72   drs2tac(B1,P,T1,T2,N1-N2,_), 
   73   drs2tac(B2,P,T2,T3,N2-N3,H2).
   74
   75drs2tac(sdrs([],Rel),P,T1,T2,N,Head):- !,
   76   conds2tac(Rel,P,T1,T2,N,Head).
   77
   78drs2tac(sdrs([D|L],R),P,T1,T3,N1-N3,H):- !,
   79   drs2tac(D,P,T1,T2,N1-N2,_),
   80   drs2tac(sdrs(L,R),P,T2,T3,N2-N3,H).
   81
   82drs2tac(lab(K,B),P,T1,[replace(K,H)|T2],N1-N2,H):- !,
   83   drs2tac(B,P,T1,T2,N1-N2,H).
   84
   85drs2tac(sub(B1,B2),P,T1,T3,N1-N3,H):-
   86   drs2tac(B1,P,T1,T2,N1-N2,H),
   87   drs2tac(B2,P,T2,T3,N2-N3,_).
   88
   89
   90/* ========================================================================
   91   Translate DRS-Conditions into TACITUS formulas (wrapper)
   92======================================================================== */
   93
   94conds2tac(Conds,P,T1,T2,N,Head):- 
   95   roles(Conds,Roles,NewConds),   
   96   conds2tac(NewConds,P,Roles,T1,T2,N,[],Head).
   97 
   98
   99/* ========================================================================
  100   Translate DRS-Conditions into TACITUS formulas 
  101======================================================================== */
  102  
  103conds2tac([],_,_,T1,T2,N-N,Heads,Head):- !,
  104   adjustMods(Heads,T1,T2),
  105   pickHead(Heads,Head).
  106
  107conds2tac([Cond|L],P,Roles,T1,T3,N1-N3,Heads,Head):-
  108   cond2tac(Cond,P,Roles,T1,T2,N1-N2,E), 
  109   conds2tac(L,P,Roles,T2,T3,N2-N3,[E|Heads],Head).
  110
  111
  112/* ========================================================================
  113   Make a guess as to what the head of a list of DRS-conditions is...
  114======================================================================== */
  115
  116pickHead(Heads,Event):- 
  117   member(closing:_:Event,Heads), !.
  118
  119pickHead(Heads,Event):- 
  120   member(event:[I]:Event,Heads),
  121   \+ (member(event:[J]:_,Heads), J < I), !.
  122
  123pickHead([_:_:Head|_],Head):- !.
  124
  125pickHead(_,_).
  126
  127
  128/* ========================================================================
  129   Adjust modifier modifiers...
  130======================================================================== */
  131
  132adjustMods(Heads,T1,T3):-
  133   select(mod:[P1]:E1,Heads,Rest),
  134   member(mod:[P2]:E2,Rest), 
  135   P1 < P2,
  136   select(Mod1,T1,T2), Mod1 =.. [Sym,E1,E],
  137   member(Mod2,T2),    Mod2 =.. [_,E2,E], !,
  138   Mod =.. [Sym,E1,E2],
  139   adjustMods(Heads,[Mod|T2],T3).
  140
  141adjustMods(_,T,T).
  142   
  143
  144/* ========================================================================
  145   Separate roles from other DRS-conditions
  146======================================================================== */
  147
  148roles([],[],[]).
  149roles([_:R|L1],[R|Roles],L2):- R = rel(_,_,Role,_), member(Role,[experiencer,topic,agent,patient,theme,recipient]), !, roles(L1,Roles,L2).
  150roles([Cond|L1],Roles,[Cond|L2]):- roles(L1,Roles,L2).
  151
  152
  153/* ========================================================================
  154   Translate a DRS-Condition into TACITUS formulas 
  155======================================================================== */
  156
  157cond2tac(I:nec(Drs),P,_,T1,[I:nec(E1,E2)|T2],N1-N3,complex:I:E1):- !,
  158   label(N1,e,E1,N2), 
  159   drs2tac(Drs,P,T1,T2,N2-N3,E2).
  160
  161cond2tac(I:pos(Drs),P,_,T1,[I:pos(E1,E2)|T2],N1-N3,complex:I:E1):- !,
  162   label(N1,e,E1,N2), 
  163   drs2tac(Drs,P,T1,T2,N2-N3,E2).
  164
  165cond2tac(I:not(Drs),P,_,T1,[I:not(E1,E2)|T2],N1-N3,complex:I:E1):- !,
  166   label(N1,e,E1,N2), 
  167   drs2tac(Drs,P,T1,T2,N2-N3,E2).
  168
  169cond2tac(I:prop(E,Drs),P,_,T1,[replace(E,H)|T2],N,complex:I:E):- !,
  170   drs2tac(Drs,P,T1,T2,N,H).
  171
  172cond2tac(I:or(Drs1,Drs2),P,_,T1,[I:or(E,H1,H2)|T3],N1-N4,complex:I:E):- !,
  173   label(N1,e,E,N2),
  174   drs2tac(Drs1,P,T1,T2,N2-N3,H1),
  175   drs2tac(Drs2,P,T2,T3,N3-N4,H2).
  176
  177cond2tac(I:imp(Drs1,Drs2),P,_,T1,[I:imp(E,H1,H2)|T3],N1-N4,complex:I:E):- !,
  178   label(N1,e,E,N2),
  179   drs2tac(Drs1,P,T1,T2,N2-N3,H1),
  180   drs2tac(Drs2,P,T2,T3,N3-N4,H2).
  181
  182cond2tac(I:whq(Drs1,Drs2),P,_,T1,[I:whq(E,H1,H2)|T3],N1-N4,complex:I:E):- !,
  183   label(N1,e,E,N2),
  184   drs2tac(Drs1,P,T1,T2,N2-N3,H1),
  185   drs2tac(Drs2,P,T2,T3,N3-N4,H2).
  186
  187cond2tac(I:duplex(_,Drs1,_,Drs2),P,_,T1,[I:whq(E,H1,H2)|T3],N1-N4,complex:I:E):- !,
  188   label(N1,e,E,N2),
  189   drs2tac(Drs1,P,T1,T2,N2-N3,H1),
  190   drs2tac(Drs2,P,T2,T3,N3-N4,H2).
  191
  192cond2tac(I:card(X,C,_),_,_,T,[I:card(E,X,C)|T],N1-N2,card:I:E):- !,
  193   label(N1,e,E,N2).      
  194
  195cond2tac(I:named(X,S1,Type,_),L,_,T,[I:F1,I:F2|T],N1-N3,named:I:E1):- !,
  196   label(N1,e,E1,N2),      
  197   label(N2,e,E2,N3),      
  198   pos(I,L,Pos),
  199   atom_concat(S1,Pos,S2),
  200   F1 =.. [S2,E1,X],
  201   F2 =.. [Type,E2,X].
  202
  203cond2tac(I:timex(X,D1),_,_,T,[I:F|T],N1-N2,timex:I:E):-
  204   timex(D1,D2),
  205   label(N1,e,E,N2),      
  206   F =.. [D2,E,X], !.
  207
  208cond2tac(I:eq(X,Y),_,_,T,[I:equal(E,X,Y)|T],N1-N2,equal:I:E):- !,
  209   label(N1,e,E,N2).      
  210
  211cond2tac(I:pred(X,closing,v,99),_,_,T,T,N-N,closing:I:X):- !.
  212
  213cond2tac(I:pred(X,S1,r,_),L,_,T,[I:F|T],N1-N2,mod:I:E):- !,
  214   pos(I,L,Pos),
  215   label(N1,e,E,N2),      
  216   atom_concat(S1,Pos,S2),
  217   F =.. [S2,E,X].
  218
  219cond2tac(I:pred(X,S1,n,_),L,_,T,[I:F|T],N1-N2,noun:I:E):- !,
  220   pos(I,L,Pos),
  221   label(N1,e,E,N2),      
  222   atom_concat(S1,Pos,S2),
  223   F =.. [S2,E,X].
  224
  225cond2tac(I:pred(E,S1,v,_),L,Roles,T,[I:F|T],N,event:I:E):- 
  226   pos(I,L,Pos), member(Pos,['-a','-r']), !,
  227   atom_concat(S1,Pos,S2),
  228   F =.. [S2,E,_,_,_],
  229   addRoles(Roles,E,F,N).
  230
  231cond2tac(I:pred(E,S1,v,_),L,Roles,T,[I:F|T],N,event:I:E):- !, 
  232   pos(I,L,Pos),
  233   atom_concat(S1,Pos,S2),
  234   F =.. [S2,E,_,_,_],
  235   addRoles(Roles,E,F,N).
  236
  237cond2tac(I:pred(E,S1,a,_),L,Roles,T,[I:F|T],N,mod:I:E):- 
  238   pos(I,L,Pos),
  239   atom_concat(S1,Pos,S2),
  240   F =.. [S2,E,_],
  241   addRoles(Roles,E,F,N), !.
  242
  243cond2tac(I:pred(X,S1,a,_),L,_,T,[I:F|T],N1-N2,mod:I:E):- !,
  244   pos(I,L,Pos),
  245   label(N1,e,E,N2),      
  246   atom_concat(S1,Pos,S2),
  247   F =.. [S2,E,X].
  248
  249cond2tac(I:rel(X,Y,P1,_),L,_,T,[I:F|T],N1-N2,rel:I:E):- !,
  250   pos(I,L,Pos),
  251   label(N1,e,E,N2),      
  252   atom_concat(P1,Pos,P2),
  253   F=..[P2,E,X,Y].
  254
  255cond2tac(I:rel(X,Y,P1),L,_,T,[I:F|T],N1-N2,rel:I:E):- !,
  256   pos(I,L,Pos),
  257   label(N1,e,E,N2),      
  258   atom_concat(P1,Pos,P2),
  259   F=..[P2,E,X,Y].
  260
  261cond2tac(I:X,_,_,T,T,N-N,unknown:I:_):-
  262   warning('cond2tac/3 failed for ~p',[X]).
  263
  264
  265/* ========================================================================
  266   Add roles as arguments
  267======================================================================== */
  268
  269addRoles([],_,F,N1-N4):- 
  270   F =.. [_,_,A1,A2,A3], !,
  271   label(N1,u,A1,N2),   
  272   label(N2,u,A2,N3),   
  273   label(N3,u,A3,N4).
  274
  275addRoles([],_,F,N1-N2):- 
  276   F =.. [_,_,A], !,
  277   label(N1,u,A,N2).
  278
  279addRoles([rel(E,X,agent,0)|L],E,F,N):-
  280   F =.. [_,E,X,_,_], !,
  281   addRoles(L,E,F,N).
  282
  283addRoles([rel(E,X,patient,0)|L],E,F,N):-
  284   F =.. [_,E,_,X,_], !,
  285   addRoles(L,E,F,N).
  286
  287addRoles([rel(E,X,recipient,0)|L],E,F,N):-
  288   F =.. [_,E,_,X,_], !,
  289   addRoles(L,E,F,N).
  290
  291addRoles([rel(E,X,topic,0)|L],E,F,N):-
  292   F =.. [_,E,_,_,X], !,
  293   addRoles(L,E,F,N).
  294
  295addRoles([rel(E,X,theme,0)|L],E,F,N):-
  296   F =.. [_,E,_,_,X], !,
  297   addRoles(L,E,F,N).
  298
  299addRoles([rel(E,X,Role,0)|L],E,F,N):-
  300   member(Role,[experiencer,topic,agent,patient,theme,recipient]),
  301   F =.. [_,E,X], !,
  302   addRoles(L,E,F,N).
  303
  304addRoles([_|L],E,F,N):-
  305   addRoles(L,E,F,N).
  306
  307
  308/*========================================================================
  309   Time Expressions
  310========================================================================*/
  311
  312timex(date(_:_,_:Y,_:M,_:D),Timex):- !,
  313   timex(date(Y,M,D),Timex).
  314
  315timex(date(_:Y,_:M,_:D),Timex):- !,
  316   timex(date(Y,M,D),Timex).
  317
  318timex(time(_:H,_:M,_:S),Timex):- !,
  319   timex(time(H,M,S),Timex).
  320
  321timex(date(Y,M,D),Timex):-
  322   year(Y,[Y1,Y2,Y3,Y4]),
  323   month(M,[M1,M2]),
  324   day(D,[D1,D2]),
  325   name(Timex,[116,95,Y1,Y2,Y3,Y4,M1,M2,D1,D2]).
  326
  327timex(time(H,M,S),Timex):-
  328   hour(H,[H1,H2]),
  329   minute(M,[M1,M2]),
  330   second(S,[S1,S2]),
  331   name(Timex,[116,95,H1,H2,M1,M2,S1,S2]).
  332
  333
  334/* ========================================================================
  335   Time Expressions (year)
  336======================================================================== */
  337
  338year(Y,C):- var(Y), !, name('XXXX',C).
  339year(Y,C):- name(Y,C).
  340
  341
  342/* ========================================================================
  343   Time Expressions (month)
  344======================================================================== */
  345
  346month(Y,C):- var(Y), !, name('XX',C).
  347month(Y,C):- name(Y,C).
  348
  349
  350/* ========================================================================
  351   Time Expressions (day)
  352======================================================================== */
  353
  354day(Y,C):- var(Y), !, name('XX',C).
  355day(Y,C):- name(Y,C).
  356
  357
  358/* ========================================================================
  359   Time Expressions (other)
  360======================================================================== */
  361
  362hour(A,C):- day(A,C).
  363minute(A,C):- day(A,C).
  364second(A,C):- day(A,C).
  365
  366
  367/* ========================================================================
  368   Determine POS
  369======================================================================== */
  370
  371pos(Is,T,POS):-
  372   member(I,Is),
  373   member(I:Tags,T),
  374   member(pos:Tag,Tags),
  375   mappos(Tag,POS), !.
  376
  377pos(_,_,'').
  378
  379
  380/* ========================================================================
  381   Map POS tags
  382======================================================================== */
  383
  384mappos('NN',  '-n').
  385mappos('NNS', '-n').
  386mappos('NNP', '-n').
  387mappos('NNPS','-n').
  388
  389mappos('VB',  '-v').
  390mappos('VBD', '-v').
  391mappos('VBG', '-v').
  392mappos('VBN', '-v').
  393mappos('VBP', '-v').
  394mappos('VBZ', '-v').
  395mappos('EX',  '-v').
  396
  397mappos('JJ',  '-a').
  398mappos('JJR', '-a').
  399mappos('JJS', '-a').
  400mappos('SO',  '-a').
  401
  402mappos('IN',  '-p').
  403mappos('POS', '-p').
  404
  405mappos('RB',  '-r').
  406mappos('RBR', '-r').
  407mappos('RBS', '-r').
  408mappos('RP',  '-r').
  409
  410
  411/* ========================================================================
  412   Print TACITUS formula
  413======================================================================== */
  414
  415printTAC([],Stream):- !, nl(Stream).
  416printTAC([X],Stream):- !, write(Stream,X), nl(Stream).
  417printTAC([X,Y|L],Stream):- write(Stream,X), write(Stream,' & '), printTAC([Y|L],Stream)