2
    3:- dynamic sem/3, tok/3, freq/2, ex/3, inex/3, pos/2.    4
    8
    9file_search_path(semlib,     'src/prolog/lib').
   10file_search_path(boxer,      'src/prolog/boxer').
   11file_search_path(knowledge,  'src/prolog/boxer/knowledge').
   12file_search_path(lex,        'src/prolog/boxer/lex').
   13
   14
   18
   21:- use_module(boxer(betaConversionDRT),[betaConvert/2]).   22
   23:- use_module(library(lists),[member/2,append/3,select/3]).   24
   25:- use_module(semlib(der),[der/2]).   26:- use_module(semlib(options),[option/2,parseOptions/2,setOption/3,
   27                               showOptions/1,setDefaultOptions/1]).   28
   29
   33
   34printTypedVar(V,Stream):- var(V), !, write(Stream,'X').
   35printTypedVar(e,Stream):- !, write(Stream,x).
   36printTypedVar(t,Stream):- !, write(Stream,'B').
   37printTypedVar(type(e,t),Stream):- !, write(Stream,'p').
   38printTypedVar(type(type(type(e,t),t),type(type(e,t),t)),Stream):- !, write(Stream,'v').
   39printTypedVar(type(type(e,t),t),Stream):- !, write(Stream,'n').
   40printTypedVar(_,Stream):- write(Stream,u).
   41
   42
   46
   48
   49addTypes('$VAR'(Id),Type,L-L,t(Type,'$VAR'(Id))):-
   50    member('$VAR'(Id):Type,L), !.
   51
   52addTypes(merge(B1,B2),t,L1-L3,merge(C1,C2)):- !, 
   53   addTypes(B1,t,L1-L2,C1),
   54   addTypes(B2,t,L2-L3,C2).
   55
   56addTypes(smerge(B1,B2),t,L1-L3,smerge(C1,C2)):- !, 
   57   addTypes(B1,t,L1-L2,C1),
   58   addTypes(B2,t,L2-L3,C2).
   59
   60addTypes(alfa(Type,B1,B2),t,L1-L3,alfa(Type,C1,C2)):- !, 
   61   addTypes(B1,t,L1-L2,C1),
   62   addTypes(B2,t,L2-L3,C2).
   63
   64addTypes(drs([],C1),t,L-L,drs([],C2)):- !,
   65   addTypesConds(C1,L,C2).
   66
   67addTypes(drs([_:D|D1],C1),t,L1-L2,drs([t(e,D)|D2],C2)):- !,
   68   addTypes(drs(D1,C1),t,[D:e|L1]-L2,drs(D2,C2)).
   69
   70addTypes(lam(X,B1),type(Alfa,Beta),L1-L2,lam(t(Alfa,X),B2)):- !,
   71   addTypes(B1,Beta,[X:Alfa|L1]-L2,B2).
   72
   73addTypes(app(E1,F1),Beta,L-L,app(E2,F2)):- !,
   74   addTypes(E1,type(Alfa,Beta),L-_,E2),
   75   addTypes(F1,Alfa,L-_,F2).
   76
   77addTypes(Exp,Type,L-L,_):- !,
   78   write('%%% unknown (addTypes/4): '), write(Exp), tab(1), write(Type), tab(1), write(L), nl,
   79   fail.
   80
   81addTypesConds([],_,[]):- !.
   82
   83addTypesConds([_:C1|L1],L,[C2|L2]):-
   84   addTypesCond(C1,L,C2),
   85   addTypesConds(L1,L,L2).
   86
   87addTypesCond(pos(B1),L,pos(B2)):- !, addTypes(B1,t,L-_,B2).
   88addTypesCond(nec(B1),L,nec(B2)):- !, addTypes(B1,t,L-_,B2).
   89addTypesCond(not(B1),L,not(B2)):- !, addTypes(B1,t,L-_,B2).
   90addTypesCond(prop(X,B1),L,prop(Y,B2)):- !, addTypeVar(X,L,Y), addTypes(B1,t,L-_,B2).
   91addTypesCond(or(B1,B2),L,or(B3,B4)):- !, addTypes(B1,t,L-_,B3), addTypes(B2,t,L-_,B4).
   92addTypesCond(imp(B1,B2),L,imp(B3,B4)):- !, addTypes(B1,t,L-L1,B3), addTypes(B2,t,L1-_,B4).
   93addTypesCond(whq(B1,B2),L,whq(B3,B4)):- !, addTypes(B1,t,L-L1,B3), addTypes(B2,t,L1-_,B4).
   94addTypesCond(duplex(X,B1,Y,B2),L,duplex(X,B3,Y,B4)):- !, addTypes(B1,t,L-L1,B3), addTypes(B2,t,L1-_,B4).
   95
   96addTypesCond(card(X,A,B),L,card(Y,A,B)):- !, addTypeVar(X,L,Y).
   97addTypesCond(named(X,A,B,C),L,named(Y,A,B,C)):- !, addTypeVar(X,L,Y).
   98addTypesCond(timex(X,A),L,timex(Y,A)):- !, addTypeVar(X,L,Y).
   99addTypesCond(eq(X,Y),L,eq(X1,Y1)):- !, addTypeVar(X,L,X1), addTypeVar(Y,L,Y1).
  100addTypesCond(rel(X,Y,A,B),L,rel(X1,Y1,A,B)):- !, addTypeVar(X,L,X1), addTypeVar(Y,L,Y1).
  101addTypesCond(role(X,Y,A,B),L,role(X1,Y1,A,B)):- !, addTypeVar(X,L,X1), addTypeVar(Y,L,Y1).
  102addTypesCond(pred(X,A,B,C),L,pred(Y,A,B,C)):- !, addTypeVar(X,L,Y).
  103
  104addTypeVar(X,L,t(T,X)):- member(X:T,L), !.
  105addTypeVar(X,_,t(u,X)).
  106
  107
  111
  112drs2tex(Drs,Type,Stream):-
  113   addTypes(Drs,Type,[]-_,TypedDrs), !, 
  114   drs2tex(TypedDrs,Stream).
  115
  116drs2tex(X,_,Stream):-
  117   write(Stream,unknown), nl(Stream),
  118   write(Stream,'%%% unknown (drs2tex/3): '), write(Stream,X), nl(Stream).
  119
  120
  124
  125drs2tex(t(Type,'$VAR'(Id)),Stream):- 
  126   printTypedVar(Type,Stream),
  127   write(Stream,'$_{'), write(Stream,Id), write(Stream,'}$').
  128
  129drs2tex(smerge(B1,B2),Stream):- !, 
  130   drs2tex(merge(B1,B2),Stream).
  131
  132drs2tex(alfa(_,B1,B2),Stream):- !, 
  133   write(Stream,'('), drs2tex(B1,Stream), 
  134   write(Stream,'$\\alpha$'), drs2tex(B2,Stream), write(Stream,')').
  135
  136drs2tex(merge(B1,B2),Stream):- !, 
  137   write(Stream,'('), drs2tex(B1,Stream),
  138   write(Stream,';'), drs2tex(B2,Stream), write(Stream,')').
  139
  140drs2tex(drs(D,C),Stream):- !,
  141   write(Stream,'\\drs{'), refs2tex(D,Stream),
  142   write(Stream,'{'), conds2tex(C,Stream), write(Stream,'}').
  143
  144drs2tex(lam(X,B),Stream):- !, 
  145   write(Stream,'$\\lambda$'), drs2tex(X,Stream),
  146   write(Stream,'.'), drs2tex(B,Stream).
  147
  148drs2tex(app(B1,B2),Stream):- !, 
  149   write(Stream,'('), drs2tex(B1,Stream),
  150   write(Stream,'@'), drs2tex(B2,Stream), write(Stream,')').
  151
  152drs2tex(X,Stream):- !,
  153   write(Stream,unknown), nl(Stream),
  154   write(Stream,'%%% unknown (drs2tex/2): '), write(Stream,X), nl(Stream).
  155
  156
  160
  161refs2tex([],Stream):- !, write(Stream,'}').
  162
  163refs2tex([C],Stream):- !, drs2tex(C,Stream), write(Stream,'}').
  164
  165refs2tex([C|L],Stream):- drs2tex(C,Stream), write(Stream,' '), refs2tex(L,Stream).
  166
  167
  171
  172conds2tex([],_):- !.
  173
  174conds2tex([C],Stream):- !,
  175   cond2tex(C,Stream,_), 
  176   write(Stream,'\\\\[-7pt]').
  177
  178conds2tex([C|Cs],Stream):-
  179   cond2tex(C,Stream,N), 
  180   format(Stream,'\\\\[~ppt]~n',[N]),
  181   conds2tex(Cs,Stream).
  182
  183
  187
  188cond2tex(not(Drs),Stream,9):- !,
  189   write(Stream,'$\\lnot$'),
  190   drs2tex(Drs,Stream).
  191
  192cond2tex(pos(Drs),Stream,9):- !,
  193   write(Stream,'$\\Diamond$'),
  194   drs2tex(Drs,Stream).
  195
  196cond2tex(nec(Drs),Stream,9):- !,
  197   write(Stream,'$\\Box$'),
  198   drs2tex(Drs,Stream).
  199 
  200cond2tex(prop(X,Drs),Stream,9):- !,
  201   drs2tex(X,Stream),
  202   write(Stream,':'),
  203   drs2tex(Drs,Stream).
  204
  205cond2tex(or(Drs1,Drs2),Stream,9):- !,
  206   drs2tex(Drs1,Stream),
  207   write(Stream,'$\\lor$'),
  208   drs2tex(Drs2,Stream).
  209
  210cond2tex(imp(Drs1,Drs2),Stream,9):- !,
  211   drs2tex(Drs1,Stream),
  212   write(Stream,'$\\Rightarrow$'),
  213   drs2tex(Drs2,Stream).
  214
  215cond2tex(whq(Drs1,Drs2),Stream,9):- !,
  216   drs2tex(Drs1,Stream),
  217   write(Stream,'?'),
  218   drs2tex(Drs2,Stream).
  219
  220cond2tex(duplex(_,Drs1,_,Drs2),Stream,N):- !, 
  221   cond2tex(whq(Drs1,Drs2),Stream,N).
  222
  223cond2tex(card(X,C,_),Stream,1):- !,
  224   write(Stream,'$|$'),
  225   drs2tex(X,Stream),
  226   write(Stream,'$|$ = '),
  227   write(Stream,C).
  228
  229cond2tex(named(X,C,_Type,_),Stream,1):- !,
  230   write(Stream,'nam('),
  231   drs2tex(X,Stream),
  232   write(Stream,','),
  233   printTok(C,Stream),
  236   write(Stream,')').
  237
  238cond2tex(timex(X,D1),Stream,1):- !,
  239   timex(D1,D2),
  240   write(Stream,'time('),
  241   drs2tex(X,Stream),
  242   write(Stream,')='),
  243   write(Stream,D2).
  244
  245cond2tex(eq(X,Y),Stream,1):-  !,
  246   drs2tex(X,Stream),
  247   write(Stream,' = '),
  248   drs2tex(Y,Stream).
  249
  250cond2tex(pred(X,Sym,_Type,_Sense),Stream,1):- 
  251   printTok(Sym,Stream),
  252   write(Stream,'('),
  253   drs2tex(X,Stream),
  254   write(Stream,')').
  255
  256cond2tex(rel(X,Y,temp_before,_),Stream,1):- !,
  257   drs2tex(X,Stream), write(Stream,' $<$ '), drs2tex(Y,Stream).
  258
  259cond2tex(rel(X,Y,temp_included,_),Stream,1):- !,
  260   drs2tex(X,Stream), write(Stream,' $\\subseteq$ '), drs2tex(Y,Stream).
  261
  262cond2tex(rel(X,Y,temp_abut,_),Stream,1):- !,
  263   drs2tex(X,Stream), write(Stream,' $\\supset$\\hspace*{-2pt}$\\subset$ '), drs2tex(Y,Stream).
  264
  265cond2tex(rel(X,Y,temp_overlap,_),Stream,1):- !,
  266   drs2tex(X,Stream), write(Stream,' $\\bigcirc$ '), drs2tex(Y,Stream).
  267
  268cond2tex(role(X,Y,Sym,1),Stream,1):- !, cond2tex(rel(X,Y,Sym,1),Stream,1).
  269
  270cond2tex(role(X,Y,Sym,-1),Stream,1):- !, cond2tex(rel(Y,X,Sym,1),Stream,1).
  271
  272cond2tex(rel(X,Y,Sym,_Sense),Stream,1):- !,
  273   printTok(Sym,Stream),
  274   write(Stream,'('),
  275   drs2tex(X,Stream),
  276   write(Stream,','),
  277   drs2tex(Y,Stream),
  278   write(Stream,')').
  279
  280
  284
  285timex(date(_:_,_:Y,_:M,_:D),Timex):- !, timex(date(Y,M,D),Timex).
  286
  287timex(date(_:Y,_:M,_:D),Timex):- !, timex(date(Y,M,D),Timex).
  288
  289timex(time(_:H,_:M,_:S),Timex):- !, timex(time(H,M,S),Timex).
  290
  291timex(date(Y,M,D),Timex):-
  292   year(Y,[Y1,Y2,Y3,Y4]),
  293   month(M,[M1,M2]),
  294   day(D,[D1,D2]),
  295   name(Timex,[Y1,Y2,Y3,Y4,M1,M2,D1,D2]).
  296
  297timex(time(H,M,S),Timex):-
  298   hour(H,[H1,H2]),
  299   minute(M,[M1,M2]),
  300   second(S,[S1,S2]),
  301   name(Timex,[H1,H2,M1,M2,S1,S2]).
  302
  303year(Y,C):- var(Y), !, name('XXXX',C).
  304year(Y,C):- name(Y,C).
  305
  306month(Y,C):- var(Y), !, name('XX',C).
  307month(Y,C):- name(Y,C).
  308
  309day(Y,C):- var(Y), !, name('XX',C).
  310day(Y,C):- name(Y,C).
  311
  312hour(A,C):- day(A,C).
  313minute(A,C):- day(A,C).
  314second(A,C):- day(A,C).
  315
  316
  320
(Stream):-
  322   write(Stream,'\\documentclass[10pt]{article}'), nl(Stream),
  323   nl(Stream),
  324   write(Stream,'\\usepackage{a4wide}'),           nl(Stream),
  325   write(Stream,'\\usepackage{rotating}'),         nl(Stream),
  326   write(Stream,'\\usepackage{latexsym}'),         nl(Stream),
  327   write(Stream,'\\usepackage{hyperref}'),         nl(Stream),
  328   nl(Stream),
  329   write(Stream,'\\newcommand{\\drs}[2]'),         nl(Stream),
  330   write(Stream,'{'),                              nl(Stream),
  331   write(Stream,'   \\begin{tabular}{|l|}'),       nl(Stream),
  332   write(Stream,'   \\hline'),                     nl(Stream),
  333   write(Stream,'   #1'),                          nl(Stream),
  334   write(Stream,'   \\\\'),                        nl(Stream),
  335   write(Stream,'   ~ \\vspace{-2ex} \\\\'),       nl(Stream),
  336   write(Stream,'   \\hline'),                     nl(Stream),
  337   write(Stream,'   ~ \\vspace{-2ex} \\\\'),       nl(Stream),
  338   write(Stream,'   #2'),                          nl(Stream),
  339   write(Stream,'   \\\\'),                        nl(Stream),
  340   write(Stream,'   \\hline'),                     nl(Stream),
  341   write(Stream,'   \\end{tabular}'),              nl(Stream),
  342   write(Stream,'}'),                              nl(Stream),
  343   nl(Stream),
  344   write(Stream,'\\parindent 0pt'),                nl(Stream),
  345   write(Stream,'\\parskip 7pt'),                  nl(Stream),
  346   write(Stream,'\\tabcolsep 1pt'),                nl(Stream),
  347   write(Stream,'%\\pdfpageheight 250mm'),         nl(Stream),
  348   write(Stream,'%\\pdfpagewidth  700mm'),         nl(Stream),
  349   write(Stream,'\\textheight 240mm'),             nl(Stream),
  350   write(Stream,'\\textwidth 184mm'),              nl(Stream),
  351   write(Stream,'\\topmargin -12mm'),              nl(Stream),
  352   write(Stream,'\\oddsidemargin -10mm'),          nl(Stream),
  353   write(Stream,'\\evensidemargin -10mm'),         nl(Stream),
  354   write(Stream,'\\pagestyle{myheadings}'),        nl(Stream), nl(Stream),
  355   write(Stream,'\\makeindex  %% makeindex derivation.idx'),   nl(Stream),
  356   write(Stream,'\\title{A large-scale, formal semantic lexicon (appendix)}'), nl(Stream),
  357   write(Stream,'\\author{Johan Bos}'),            nl(Stream),
  358   write(Stream,'\\begin{document}'),              nl(Stream),
  359   write(Stream,'\\maketitle'),                    nl(Stream),   
  360   write(Stream,'\\thispagestyle{empty}'),         nl(Stream),
  361   write(Stream,'%\\tableofcontents'),             nl(Stream),
  362   write(Stream,'\\input{intro}'),                 nl(Stream),
  363   nl(Stream).
  364
(Stream):-
  366   write(Stream,'\\markright{\\rm Appendix: Index \\hfill Page~}'), nl(Stream),
  367   write(Stream,'\\input{derivation.ind}'),        nl(Stream),
  368   write(Stream,'\\end{document}'),                nl(Stream).   
  369
  370
  374
  375cat2type(t:_,    t):- !.
  376cat2type(n,      type(e,t)):- !.
  377cat2type(n:_,    type(e,t)):- !.
  378cat2type(pp,     type(e,t)):- !.
  379cat2type(np,     type(type(e,t),t)):- !.
  380cat2type(np_exp, type(type(e,t),t)):- !.
  381cat2type(np_thr, type(type(e,t),t)):- !.
  382cat2type(s:_,    type(type(e,t),t)):- !.
  383cat2type(comma,  type(t,type(t,t))):- !.
  384cat2type(semi,   type(t,type(t,t))):- !.
  385cat2type(conj,   type(t,type(t,t))):- !.
  386
  387cat2type(conj:app, type(X,type(X,X))):- !, cat2type(np,X).
  388
  389cat2type('\\'(A,B), type(BType,AType) ):- !, cat2type(A,AType), cat2type(B,BType).
  390cat2type('/'(A,B), type(BType,AType) ):- !, cat2type(A,AType), cat2type(B,BType).
  391
  392
  396
  397cleanCat('\\'(A1,B1), '\\'(A2,B2) ):- !, cleanCat(A1,A2), cleanCat(B1,B2).
  398cleanCat('/'(A1,B1),  '/'(A2,B2)  ):- !, cleanCat(A1,A2), cleanCat(B1,B2).
  399cleanCat(n:_,n):- !.
  400cleanCat(comma,conj):- !.
  401cleanCat(semi,conj):- !.
  403cleanCat(X,X).
  404
  405
  409
  410printCat('\\'(A,B),Stream):- !,
  411   write(Stream,'('),
  412   printCat(A,Stream),
  413   write(Stream,'$\\backslash$'),
  414   printCat(B,Stream),
  415   write(Stream,')').
  416
  417printCat('/'(A,B),Stream):- !,
  418   write(Stream,'('),
  419   printCat(A,Stream),
  420   write(Stream,'/'),
  421   printCat(B,Stream),
  422   write(Stream,')').
  423
  424printCat(np_thr,Stream):- !, write(Stream,'NP[thr]').
  425
  426printCat(np_exp,Stream):- !, write(Stream,'NP[exp]').
  427
  428printCat(comma,Stream):- !, write(Stream,'CONJ').
  429
  430printCat(semi,Stream):- !, write(Stream,'CONJ').
  431
  432printCat(n:_,Stream):- !,
  433   write(Stream,'N').
  434
  435printCat(Cat:Fea,Stream):- 
  436   var(Fea), !, Fea = 'X', 
  437   printCat(Cat:Fea,Stream).
  438
  439printCat(Cat:Fea,Stream):- 
  440   atom(Cat), atom(Fea), !,
  441   upcase_atom(Cat,Up),
  442   write(Stream,Up), write(Stream,'['),
  443   write(Stream,Fea), write(Stream,']').
  444
  445printCat(Cat,Stream):- 
  446   atom(Cat), !,
  447   upcase_atom(Cat,Up),
  448   write(Stream,Up).
  449
  450printCat(Cat,Stream):- 
  451   write(Stream,Cat).
  452
  453
  457
  458printType(type(A,B),Stream):- !,
  459   write(Stream,'$\\langle$'),
  460   printType(A,Stream),
  461   write(Stream,','),
  462   printType(B,Stream),
  463   write(Stream,'$\\rangle$').
  464
  465printType(A,Stream):- write(Stream,A).
  466
  467
  471
  472printExample(Id,Stream,W):-
  473  ex(Id,Ex,_),
  474  write(Stream,'('), write(Stream,Id), write(Stream,') '),
  475  printSentence(Ex,Stream,W).
  476
  477printSentence([W|Words],Stream,W):- !,
  478   write(Stream,'\\textrm{\\underline{'),
  479   printTok(W,Stream), write(Stream,'}'),
  480   printSentence1(Words,Stream,W).
  481
  482printSentence([X|Words],Stream,W):-
  483   write(Stream,'\\textrm{'),
  484   printTok(X,Stream),
  485   printSentence1(Words,Stream,W).
  486
  487printSentence1([],Stream,_):- 
  488   write(Stream,'}'), nl(Stream).
  489
  490printSentence1([W|L],Stream,W):- 
  491   member(W,['.', ',', '?', '\'re', '\'s', '\'ve', 'n\'t', '%']), !,
  492   write(Stream,'\\underline{'), printTok(W,Stream), write(Stream,'}'),
  493   printSentence1(L,Stream,W).
  494
  495printSentence1([W|L],Stream,W):- !,
  496   write(Stream,' \\underline{'), printTok(W,Stream), write(Stream,'}'),
  497   printSentence1(L,Stream,W).
  498
  499printSentence1([X|L],Stream,W):- 
  500   member(X,['.', ',', '?', '\'re', '\'s', '\'ve', 'n\'t', '%']), !,
  501   printTok(X,Stream), 
  502   printSentence1(L,Stream,W).
  503
  504printSentence1([X|L],Stream,W):-
  505   write(Stream,' '),
  506   printTok(X,Stream), 
  507   printSentence1(L,Stream,W).
  508
  509
  513
  514printTokens(Id,Stream):-
  515   findall(t(F,Tok),tok(Id,Tok,F),L),
  516   sort(L,Sorted), reverse(Sorted,Ordered),
  517   printTok(Ordered,20,Stream).
  518
  519printTok([t(F,X)|_],1,Stream):- !,
  520   printIndex(X,Stream),
  521   write(Stream,'\\textrm{'), printTok(X,Stream), write(Stream,'}$^{('),
  522   write(Stream,F), write(Stream,')}$.'),
  523   nl(Stream).
  524
  525printTok([t(F,X)],_,Stream):- !,
  526   printIndex(X,Stream),
  527   write(Stream,'\\textrm{'), printTok(X,Stream),  write(Stream,'}$^{('),
  528   write(Stream,F), write(Stream,')}$.'),
  529   nl(Stream).
  530
  531printTok([t(F,X)|L],N,Stream):- !,
  532   printIndex(X,Stream),
  533   write(Stream,'\\textrm{'), printTok(X,Stream),  write(Stream,'}$^{('),
  534   write(Stream,F), write(Stream,')}$, '),
  535   M is N - 1,
  536   printTok(L,M,Stream).
  537
  538
  539printIndex(Tok,_):-
  540   atom(Tok),
  541   atom_chars(Tok,Chars),
  542   special(Special),
  543   member(Special,Chars), !.
  544
  545printIndex(Tok,Stream):-
  546   write(Stream,'\\index{\\textrm{'), printTok(Tok,Stream), write(Stream,'}}').
  547
  548
  549printTok(Tok,Stream):-
  550   atom(Tok),
  551   atom_chars(Tok,Chars),
  552   special(Special),
  553   member(Special,Chars), !,
  554   printChars(Chars,Stream).
  555
  556printTok(Tok,Stream):-
  557   write(Stream,Tok).
  558
  559printToks([],_):- !.
  560printToks([X],Stream):- !, printTok(X,Stream).
  561printToks([X|L],Stream):- !, printTok(X,Stream), write(Stream,' '), printToks(L,Stream).
  562
  563printChars([],_).
  564printChars([Char|L],Stream):- special(Char), !, write(Stream,'\\'), write(Stream,Char), printChars(L,Stream).
  565printChars([X|L],Stream):- !, write(Stream,X), printChars(L,Stream).
  566
  567
  571
  572special('$').
  573special('%').
  574special('&').
  575special('}').
  576special('{').
  577special('#').
  578special('_').
  579
  580
  584
  585computeF:-
  586   sem(_,_,Id),
  587   \+ freq(Id,_), !,
  588   findall(F,tok(Id,_,F),L),
  589   sum(L,0,Sum),
  590   assert(freq(Id,Sum)),
  591   computeF.
  592
  593computeF.
  594
  595sum([],Sum,Sum).
  596
  597sum([X|L],Acc,Sum):-
  598   New is Acc+X,
  599   sum(L,New,Sum).
  600
  601
  605
  606printDer(Comb,Stream,Tok3):- 
  607   ( Comb = fa(Cat,Sem,L,R), !, Rule = '[$>$]'
  608   ; Comb = fc(Cat,Sem,L,R), !, Rule = '[FC]'
  609   ; Comb = gfc(Cat,Sem,L,R), !, Rule = '[GFC]'
  610   ; Comb = gbc(Cat,Sem,L,R), !, Rule = '[GBC]'
  611   ; Comb = bc(Cat,Sem,L,R), !, Rule = '[BC]'
  612   ; Comb = fs(Cat,Sem,L,R), !, Rule = '[FS]'
  613   ; Comb = bs(Cat,Sem,L,R), !, Rule = '[BS]'
  614   ; Comb = conj(Cat,Sem,L,R), !, Rule = '[CONJ]'
  615   ; Comb = bxc(Cat,Sem,L,R), !, Rule = '[BXC]'
  616   ; Comb = fxc(Cat,Sem,L,R), !, Rule = '[FXC]'
  617   ; Comb = gbxc(Cat,Sem,L,R), !, Rule = '[GBXC]'
  618   ; Comb = gfxc(Cat,Sem,L,R), !, Rule = '[GFXC]'
  619   ; Comb = fxs(Cat,Sem,L,R), !, Rule = '[BXS]'
  620   ; Comb = bxs(Cat,Sem,L,R), !, Rule = '[FXS]'
  621   ; Comb = ba(Cat,Sem,L,R), !, Rule = '[$<$]' ), 
  622   write(Stream,'\\begin{tabular}[b]{ll}'), nl(Stream),
  623   printDer(L,Stream,Tok1), write(Stream,'&'),
  624   printDer(R,Stream,Tok2), write(Stream,'\\\\'), nl(Stream),
  625   append(Tok1,Tok2,Tok3),
  626   write(Stream,'\\multicolumn{2}{c}{\\hrulefill '), write(Stream,Rule), write(Stream,'}\\\\'), nl(Stream),
  627   betaConvert(Sem,Red),
  628   cat2type(Cat,Type),
  629   numbervars(Red,1,_),
  630   write(Stream,'\\multicolumn{2}{c}{\\begin{tabular}[b]{l}'),
  631   write(Stream,'\\textbf{'), printToks(Tok3,Stream), write(Stream,'}\\\\'), nl(Stream), 
  632   printCat(Cat,Stream), write(Stream,'\\\\'), nl(Stream), 
  633   printType(Type,Stream), write(Stream,'\\\\'), nl(Stream), 
  635   drs2tex(Red,Type,Stream), 
  636   !,
  637   write(Stream,'\\end{tabular}}'), nl(Stream),
  638   write(Stream,'\\end{tabular}'), nl(Stream).
  639
  640printDer(Comb,Stream,Tok):- 
  641   ( Comb = tc(Cat,Sem,T), !, Rule = '[TC]'
  642   ; Comb = tr(Cat,Sem,T), !, Rule = '[TR]' ),
  643   write(Stream,'\\begin{tabular}[b]{c}'), nl(Stream),
  644   printDer(T,Stream,Tok), write(Stream,'\\\\'), nl(Stream),
  645   write(Stream,'\\hrulefill '), write(Stream,Rule), write(Stream,'\\\\'), nl(Stream),
  646   betaConvert(Sem,Red),
  647   cat2type(Cat,Type),
  648   numbervars(Red,1,_),
  649   write(Stream,'\\begin{tabular}[b]{l}'), nl(Stream),
  650   write(Stream,'\\textbf{'), printToks(Tok,Stream), write(Stream,'}\\\\'), nl(Stream), 
  651   printCat(Cat,Stream), write(Stream,'\\\\'), nl(Stream), 
  652   printType(Type,Stream), write(Stream,'\\\\'), nl(Stream), 
  654   drs2tex(Red,Type,Stream), 
  655   write(Stream,'\\\\'), nl(Stream), 
  656   !,
  657   write(Stream,'\\end{tabular}'), nl(Stream),
  658   write(Stream,'\\end{tabular}'), nl(Stream).
  659
  660printDer(t(Sem,Cat,Tok,_Pos),Stream,[Tok]):- 
  661   cat2type(Cat,Type),  
  662   betaConvert(Sem,Red),
  663   numbervars(Red,1,_),
  664   write(Stream,'\\begin{tabular}[b]{l}'), nl(Stream),
  665   write(Stream,'\\textbf{'), printTok(Tok,Stream), write(Stream,'}\\\\'), nl(Stream), 
  666   printCat(Cat,Stream), write(Stream,'\\\\'), nl(Stream), 
  667   printType(Type,Stream), write(Stream,'\\\\'), nl(Stream), 
  668   drs2tex(Red,Type,Stream), 
  669   write(Stream,'\\\\'), nl(Stream), 
  670   !, 
  671   write(Stream,'\\end{tabular}'), nl(Stream).
  672
  673printDer(X,Stream,[]):- !,
  674   write(Stream,unknown), nl(Stream),
  675   write(Stream,'%%% unknown (printDer): '),
  676   write(Stream,X),nl(Stream),nl(Stream).
  677
  678
  682
  683analyse(t(Sem,Cat,Tok,Pos),Index,[Tok|L]-L):- !,
  684   cleanCat(Cat,CleanCat),
  685    (    member(Pos,['NNP','NNPS']), Sym = Tok
  686    ; \+ member(Pos,['NNP','NNPS']), downcase_atom(Tok,Sym) ),
  687   betaConvert(Sem,Converted),
  688   add(CleanCat,Sym,Tok,Pos,Converted,Index).
  689
  690analyse(Tree,I,L1-L3):-
  691   Tree =.. [_Name,_Cat,_Sem,T1,T2], !,
  692   analyse(T1,I,L1-L2),
  693   analyse(T2,I,L2-L3).
  694
  695analyse(Tree,I,L1-L2):-
  696   Tree =.. [_Name,_Cat,_Sem,T], !,
  697   analyse(T,I,L1-L2).
  698
  699analyse(Tree,I,L1-L4):-
  700   Tree =.. [_Name,_Cat,_Sem,T1,T2,T3], !,
  701   analyse(T1,I,L1-L2),
  702   analyse(T2,I,L2-L3),
  703   analyse(T3,I,L3-L4).
  704
  705
  709
  710derivations:-
  711   der(N,Der), 
  712   analyse(Der,N,S-[]), 
  713   length(S,Len), 
  714   assert(ex(N,S,Len)),
  715   fail.
  716
  717derivations:- 
  718   computeF, !.
  719
  720
  724
  725printDerivations(Stream):-
  726   der(N,Der), 
  727   \+ blocked(N),
  728   minlen(MinLen),
  729   maxlen(MaxLen),
  730   ex(N,S,Len), Len < MaxLen, Len > MinLen,
  731   write(N:Len:S), nl,
  732   write(Stream,'\\clearpage'), nl(Stream),
  733   write(Stream,'\\begin{sidewaystable}\\scriptsize'), nl(Stream),
  734   printDer(Der,Stream,_),
  735   format(Stream,'\\caption{\\label{ex:~p}',[N]),
  736   printToks(S,Stream), format(Stream,' (~p)}~n',[N]),
  737   write(Stream,'\\end{sidewaystable}'), nl(Stream),
  738   fail.
  739
  740printDerivations(Stream):- 
  741   nl(Stream).
  742
  743
  747
  748add(Cat,Sym,Tok,Pos,X1,Sen):-                      
  749   sem(Cat,X2,Id),                       
  750   similar(X1,X2), !,                   751   assert(inex(Id,Sen,Tok:Sym)),
  752   (  pos(Id,Pos), !
  753   ;  assert(pos(Id,Pos))
  754   ),
  755   (  tok(Id,Sym,M), !,                 756      retract(tok(Id,Sym,M)),
  757      N is M + 1,
  758      assert(tok(Id,Sym,N)),
  759      ( tok(Id,_,Higher), Higher > N, !
  760      ; retract(sem(Cat,_,Id)),
  761        assert(sem(Cat,X1,Id))
  762      )
  763   ;  assert(tok(Id,Sym,1))             764   ).
  765   
  766add(Cat,Sym,Tok,Pos,X,Sen):-            767   \+ sem(_,_,_), !,                    768   assert(sem(Cat,X,1)),
  769   assert(inex(1,Sen,Tok:Sym)),
  770   assert(pos(1,Pos)),
  771   assert(tok(1,Sym,1)).
  772
  773add(Cat,Sym,Tok,Pos,X,Sen):-            774   sem(_,_,I),                          775   \+ (sem(_,_,J), J > I), !,           776   N is I + 1,
  777   assert(sem(Cat,X,N)),
  778   assert(inex(N,Sen,Tok:Sym)),
  779   assert(pos(N,Pos)),
  780   assert(tok(N,Sym,1)).
  781
  782
  786
  787similar(X,Y):- var(X), !, var(Y).
  788similar(X,Y):- var(Y), !, var(X).
  789similar('$VAR'(X),'$VAR'(X)).
  790
  791similar(lam(_,A),      lam(_,B)):-      similar(A,B).
  792similar(app(A1,A2),    app(B1,B2)):-    similar(A1,B1), similar(A2,B2).
  793similar(smerge(A1,A2), smerge(B1,B2)):- similar(A1,B1), similar(A2,B2).
  794similar(merge(A1,A2),  merge(B1,B2)):-  similar(A1,B1), similar(A2,B2).
  795similar(alfa(T,A1,A2), alfa(T,B1,B2)):- similar(A1,B1), similar(A2,B2).
  796
  797similar(drs(D1,C1), drs(D2,C2)):- length(D1,Len), length(D2,Len), similar(C1,C2).
  798
  799similar([],[]).
  800similar([_:C1|L1],[_:C2|L2]):- similar(C1,C2), similar(L1,L2).
  801
  802similar(not(A),    not(B)):-    similar(A,B).
  803similar(pos(A),    pos(B)):-    similar(A,B).
  804similar(nec(A),    nec(B)):-    similar(A,B).
  805similar(prop(_,A), prop(_,B)):- similar(A,B).
  806
  807similar(imp(A1,A2),     imp(B1,B2)):-     similar(A1,B1), similar(A2,B2).
  808similar(or(A1,A2),      or(B1,B2)):-      similar(A1,B1), similar(A2,B2).
  809similar(whq(A1,A2),     whq(B1,B2)):-     similar(A1,B1), similar(A2,B2).
  810similar(duplex(_,A1,_,A2), duplex(_,B1,_,B2)):- similar(A1,B1), similar(A2,B2).
  811
  812similar(card(_,_,_),    card(_,_,_)).
  813similar(timex(_,_),     timex(_,_)).
  814similar(eq(_,_),        eq(_,_)).
  815similar(pred(_,_,T,_),  pred(_,_,T,_)).
  816similar(rel(_,_,_,_),   rel(_,_,_,_)).
  817similar(role(_,_,_,_),  role(_,_,_,_)).
  818similar(named(_,_,_,_), named(_,_,_,_)).
  819
  820
  821
  825
  826blocked(201).
  827blocked(211).
  828blocked(382).
  829blocked(472).
  830blocked(522).
  831blocked(526).
  832blocked(576).
  833blocked(579).
  834blocked(616).
  835blocked(606).
  836blocked(638).
  837blocked(743).
  838blocked(772).
  839blocked(830).
  840blocked(1033).
  841blocked(1036).
  842blocked(1148).
  843blocked(1321).
  844blocked(1328).
  845blocked(1342).
  846blocked(1353).
  847blocked(1424).
  848blocked(1449).
  849blocked(1499).
  850blocked(1532).
  851blocked(1540).
  852blocked(1709).
  853
  857
  858minlen(3).
  859maxlen(10).
  860
  864
  865getExample(Id,ExId,Tok,Len):-
  866   minlen(Min),
  867   inex(Id,ExId,Tok:_),
  868   \+ blocked(ExId),
  869   ex(ExId,Ex,Len), Len > Min, 
  870   \+ ( select(Tok,Ex,NewEx), member(Tok,NewEx) ),
  871   \+ ( inex(Id,ExId1,_), \+ blocked(ExId1), ex(ExId1,_,Len1), Len1 > Min, Len1 < Len).
  872
  873getExample(Id,ExId,Tok,Len):-
  874   minlen(Min),
  875   inex(Id,ExId,Tok:_),
  876   \+ blocked(ExId),
  877   ex(ExId,_,Len), Len > Min,
  878   \+ ( inex(Id,ExId1,_), \+ blocked(ExId), ex(ExId1,_,Len1), Len1 > Min, Len1 < Len).
  879
  880getExample(Id,ExId,Tok,Len):-
  881   inex(Id,ExId,Tok:_),
  882   ex(ExId,_,Len),
  883   \+ blocked(ExId),
  884   \+ ( inex(Id,ExId1,_), \+ blocked(ExId), ex(ExId1,_,Len1), Len1 < Len).
  885
  886getExample(Id,ExId,Tok,Len):-
  887   inex(Id,ExId,Tok:_),
  888   ex(ExId,_,Len),
  889   \+ ( inex(Id,ExId1,_), ex(ExId1,_,Len1), Len1 < Len).
  890
  891
  895
  896body([],_,Stream):- !, nl(Stream).
  897
  898body([s(F,Id)|L1],N1,Stream):-
  899   F > 0,
  900   sem(Cat,X,Id), 
  901   cat2type(Cat,Type),
  902
  903   Remainder is mod(N1,2),
  904   ( Remainder = 1, write(Stream,'\\clearpage'), nl(Stream)
  905   ; Remainder = 0 ),
  906
  908   write(Stream,'\\index{\\textsf{'),
  909   printCat(Cat,Stream),    
  910   write(Stream,'}}'),nl(Stream),
  911
  912   write(Stream,'\\begin{tabular}[t]{rl}'), nl(Stream),
  913   write(Stream,'\\textbf{Category}: & \\textsf{'),
  914   printCat(Cat,Stream),    
  915   write(Stream,'}\\\\[7pt]'), nl(Stream),
  916
  917   write(Stream,'\\textbf{Type}: & '),
  918   printType(Type,Stream),   
  919   write(Stream,'\\\\[7pt]'), nl(Stream), 
  920
  921   write(Stream,'\\textbf{PoS}: & {\\small '),
  922   findall(POS,pos(Id,POS),POSs),
  923   printToks(POSs,Stream),    
  924   write(Stream,'}\\\\[7pt]'), nl(Stream), 
  925
  926   write(Stream,'\\textbf{Semantics}: & \\\\'), nl(Stream),        
  927   format(Stream,'\\end{tabular}\\hfill F=~p~n~n',[F]),
  928
  929   numbervars(X,1,_),
  930   format(Stream,'%%%~p~n',[X]), 
  931   write(Stream,'\\textsf{'), 
  932   drs2tex(X,Type,Stream), 
  933   write(Stream,'}'), nl(Stream), nl(Stream), 
  934
  935   write(Stream,'\\textbf{Most frequent lexical entries}:\\\\[2pt]'), nl(Stream),
  936   printTokens(Id,Stream),      nl(Stream), nl(Stream),        
  937
  938   write(Stream,'\\textbf{Corpus examples}:\\\\[2pt]'),   nl(Stream),
  939   printExample1(Stream,Id,Ex),
  940   printExample2(Stream,Id,Ex),
  941
  942   write(Stream,'\\vfill'),
  943   nl(Stream), nl(Stream), !,
  944
  945   ( select(s(F2,Id2),L1,L2), sem(Cat,_,Id2), !, L3=[s(F2,Id2)|L2] 
  946   ; L3 = L1 ),
  947   N2 is N1 + 1, 
  948   body(L3,N2,Stream).
  949
  950body([_|L],N,Stream):- !,
  951   body(L,N,Stream).
  952
  953
  957
(Len,Stream,N):-
  959   \+ blocked(N),
  960   maxlen(MaxLen),
  961   minlen(MinLen),
  962   Len < MaxLen, 
  963   Len > MinLen, !, 
  964   format(Stream,'(see p. \\pageref{ex:~p})~n~n',[N]).
  965
  966printPageRef(_,Stream,_):-
  967   nl(Stream).
  968
  969
  973
  974printExample1(Stream,Id,N):-
  975   tok(Id,Sym,F), 
  976   \+ (tok(Id,_,Higher), Higher > F), 
  977   inex(Id,N,Tok:Sym), 
  978   ex(N,_,Len), Len < 18, Len > 4,
  979   printExample(N,Stream,Tok), !,
  980   printPageRef(Len,Stream,N).
  981
  982printExample1(_,_,0).
  983
  984
  988
  989printExample2(Stream,Id,N):-
  990   getExample(Id,Ex,Tok,Len), \+ Ex=N,
  991   printExample(Ex,Stream,Tok), !,
  992   printPageRef(Len,Stream,Ex).
  993
  994printExample2(Stream,_,_):- 
  995   nl(Stream).
  996
  997
 1001
 1002go:-
 1003   setDefaultOptions(boxer), 
 1004   setOption(boxer,'--warnings',true),
 1005   setOption(boxer,'--roles',verbnet),
 1006
 1007   derivations,
 1008   findall(s(F,Id),freq(Id,F),All),
 1009   sort(All,Sorted),
 1010   reverse(Sorted,Ordered),
 1011
 1012   open('working/doc/derivation.tex',write,Stream),
 1013
 1014   printHeader(Stream),
 1015   write(Stream,'\\markright{\\rm Appendix: Lexicon \\hfill Page~}'),  nl(Stream),
 1016   write(Stream,'\\addcontentsline{toc}{section}{2. Lexicon}'),        nl(Stream),
 1017   body(Ordered,1,Stream),
 1018   write(Stream,'\\clearpage'),   nl(Stream),
 1019   write(Stream,'\\markright{\\rm Appendix: Derivations \\hfill Page~}'), nl(Stream),
 1020   write(Stream,'\\addcontentsline{toc}{section}{3. Derivations}'),       nl(Stream),
 1021   printDerivations(Stream),
 1022   printFooter(Stream),
 1023   close(Stream).
 1024
 1025:- go.