1/* @(#)newdic.pl	24.1 2/23/88 */
    2
    3/* 
    4	Copyright 1986, Fernando C.N. Pereira and David H.D. Warren,
    5
    6			   All Rights Reserved
    7*/
    8% Modes
    9
   10:- mode word(+).   11:- mode ~(+).   12:- mode conj(+).   13:- mode adverb(+).   14:- mode sup_adj(+,?).   15:- mode rel_adj(+,?).   16:- mode adj(+,?).   17:- mode name_template(+,-).   18:- mode name(+).   19:- mode terminator(+,?).   20:- mode pers_pron(+,?,?,?,?).   21:- mode poss_pron(+,?,?,?).   22:- mode rel_pron(+,?).   23:- mode regular_past(+,?).   24:- mode regular_pres(+).   25:- mode verb_root(+).   26:- mode verb_form(+,?,?,?).   27:- mode noun_sin(+).   28:- mode noun_plu(+,?).   29:- mode noun_form(+,?,?).   30:- mode prep(+).   31:- mode quantifier_pron(+,?,?).   32:- mode tr_number(+,?).   33:- mode number(+,?,?).   34:- mode det(+,?,?,?).   35:- mode int_art(+,?,?,?).   36:- mode int_pron(+,?).   37
   38% =================================================================
   39% General Dictionary
   40
   41word(Word) :- ~(Word).
   42word(Word) :- conj(Word).
   43word(Word) :- adverb(Word).
   44word(Word) :- sup_adj(Word,_).
   45word(Word) :- rel_adj(Word,_).
   46word(Word) :- adj(Word,_).
   47word(Word) :- name(Word).
   48word(Word) :- terminator(Word,_).
   49word(Word) :- pers_pron(Word,_,_,_,_).
   50word(Word) :- poss_pron(Word,_,_,_).
   51word(Word) :- rel_pron(Word,_).
   52word(Word) :- verb_form(Word,_,_,_).
   53word(Word) :- noun_form(Word,_,_).
   54word(Word) :- prep(Word).
   55word(Word) :- quantifier_pron(Word,_,_).
   56word(Word) :- number(Word,_,_).
   57word(Word) :- det(Word,_,_,_).
   58word(Word) :- int_art(Word,_,_,_).
   59word(Word) :- int_pron(Word,_).
   60word(Word) :- loc_pred(Word,_).
   61
   62~how.
   63~whose.
   64~there.
   65~of.
   66~('''').
   67~(',').
   68~s.
   69~than.
   70~at.
   71~the.
   72~not.
   73~(as).
   74~that.
   75~less.
   76~more.
   77~least.
   78~most.
   79~many.
   80~where.
   81~when.
   82conj(and).
   83conj(or).
   84
   85int_pron(what,undef).
   86int_pron(which,undef).
   87int_pron(who,subj).
   88int_pron(whom,compl).
   89
   90int_art(what,X,_,int_det(X)).
   91int_art(which,X,_,int_det(X)).
   92
   93det(the,No,the(No),def).
   94det(a,sg,a,indef).
   95det(an,sg,a,indef).
   96det(every,sg,every,indef).
   97det(some,_,some,indef).
   98det(any,_,any,indef).
   99det(all,plu,all,indef).
  100det(each,sg,each,indef).
  101det(no,_,no,indef).
  102
  103number(W,I,Nb) :-
  104   tr_number(W,I),
  105   ag_number(I,Nb).
  106
  107tr_number(nb(I),I).
  108tr_number(one,1).
  109tr_number(two,2).
  110tr_number(three,3).
  111tr_number(four,4).
  112tr_number(five,5).
  113tr_number(six,6).
  114tr_number(seven,7).
  115tr_number(eight,8).
  116tr_number(nine,9).
  117tr_number(ten,10).
  118
  119ag_number(1,sg).
  120ag_number(N,plu) :- N>1.
  121
  122quantifier_pron(everybody,every,person).
  123quantifier_pron(everyone,every,person).
  124quantifier_pron(everything,every,thing).
  125quantifier_pron(somebody,some,person).
  126quantifier_pron(someone,some,person).
  127quantifier_pron(something,some,thing).
  128quantifier_pron(anybody,any,person).
  129quantifier_pron(anyone,any,person).
  130quantifier_pron(anything,any,thing).
  131quantifier_pron(nobody,no,person).
  132quantifier_pron(nothing,no,thing).
  133
  134prep(as).
  135prep(at).
  136prep(of).
  137prep(to).
  138prep(by).
  139prep(with).
  140prep(in).
  141prep(on).
  142prep(from).
  143prep(into).
  144prep(through).
  145
  146noun_form(Plu,Sin,plu) :- noun_plu(Plu,Sin).
  147noun_form(Sin,Sin,sg) :- noun_sin(Sin).
  148
  149verb_form(V,V,inf,_) :- verb_root(V).
  150verb_form(V,V,pres+fin,Agmt) :-
  151   regular_pres(V),
  152   root_form(Agmt),
  153   verb_root(V).
  154verb_form(Past,Root,past+_,_) :-
  155   regular_past(Past,Root).
  156
  157root_form(1+sg).
  158root_form(2+_).
  159root_form(1+plu).
  160root_form(3+plu).
  161
  162verb_root(be).
  163verb_root(have).
  164verb_root(do).
  165
  166verb_form(am,be,pres+fin,1+sg).
  167verb_form(are,be,pres+fin,2+sg).
  168verb_form(is,be,pres+fin,3+sg).
  169verb_form(are,be,pres+fin,_+plu).
  170verb_form(was,be,past+fin,1+sg).
  171verb_form(were,be,past+fin,2+sg).
  172verb_form(was,be,past+fin,3+sg).
  173verb_form(were,be,past+fin,_+plu).
  174verb_form(been,be,past+part,_).
  175verb_form(being,be,pres+part,_).
  176
  177verb_type(be,aux+be).
  178
  179regular_pres(have).
  180
  181regular_past(had,have).
  182
  183verb_form(has,have,pres+fin,3+sg).
  184verb_form(having,have,pres+part,_).
  185
  186verb_type(have,aux+have).
  187
  188regular_pres(do).
  189
  190verb_form(does,do,pres+fin,3+sg).
  191verb_form(did,do,past+fin,_).
  192verb_form(doing,do,pres+part,_).
  193verb_form(done,do,past+part,_).
  194
  195verb_type(do,aux+ditrans).
  196
  197rel_pron(who,subj).
  198rel_pron(whom,compl).
  199rel_pron(which,undef).
  200
  201poss_pron(my,_,1,sg).
  202poss_pron(your,_,2,_).
  203poss_pron(his,masc,3,sg).
  204poss_pron(her,fem,3,sg).
  205poss_pron(its,neut,3,sg).
  206poss_pron(our,_,1,plu).
  207poss_pron(their,_,3,plu).
  208
  209pers_pron(i,_,1,sg,subj).
  210pers_pron(you,_,2,_,_).
  211pers_pron(he,masc,3,sg,subj).
  212pers_pron(she,fem,3,sg,subj).
  213pers_pron(it,neut,3,sg,_).
  214pers_pron(we,_,1,plu,subj).
  215pers_pron(them,_,3,plu,subj).
  216pers_pron(me,_,1,sg,compl(_)).
  217pers_pron(him,masc,3,sg,compl(_)).
  218pers_pron(her,fem,3,sg,compl(_)).
  219pers_pron(us,_,1,plu,compl(_)).
  220pers_pron(them,_,3,plu,compl(_)).
  221
  222terminator(.,_).
  223terminator(?,?).
  224terminator(!,!).
  225
  226name(Name) :-
  227   name_template(Name,_), !.
  228
  229% =================================================================
  230% Specialised Dictionary
  231
  232loc_pred(east,prep(eastof)).
  233loc_pred(west,prep(westof)).
  234loc_pred(north,prep(northof)).
  235loc_pred(south,prep(southof)).
  236
  237adj(minimum,restr).
  238adj(maximum,restr).
  239adj(average,restr).
  240adj(total,restr).
  241adj(african,restr).
  242adj(american,restr).
  243adj(asian,restr).
  244adj(european,restr).
  245adj(great,quant).
  246adj(big,quant).
  247adj(small,quant).
  248adj(large,quant).
  249adj(old,quant).
  250adj(new,quant).
  251adj(populous,quant).
  252
  253rel_adj(greater,great).
  254rel_adj(less,small).
  255rel_adj(bigger,big).
  256rel_adj(smaller,small).
  257rel_adj(larger,large).
  258rel_adj(older,old).
  259rel_adj(newer,new).
  260
  261sup_adj(biggest,big).
  262sup_adj(smallest,small).
  263sup_adj(largest,large).
  264sup_adj(oldest,old).
  265sup_adj(newest,new).
  266
  267noun_form(proportion,proportion,_).
  268noun_form(percentage,percentage,_).
  269
  270noun_sin(average).
  271noun_sin(total).
  272noun_sin(sum).
  273noun_sin(degree).
  274noun_sin(sqmile).
  275noun_sin(ksqmile).
  276noun_sin(thousand).
  277noun_sin(million).
  278noun_sin(time).
  279noun_sin(place).
  280noun_sin(area).
  281noun_sin(capital).
  282noun_sin(city).
  283noun_sin(continent).
  284noun_sin(country).
  285noun_sin(latitude).
  286noun_sin(longitude).
  287noun_sin(ocean).
  288noun_sin(person).
  289noun_sin(population).
  290noun_sin(region).
  291noun_sin(river).
  292noun_sin(sea).
  293noun_sin(seamass).
  294noun_sin(number).
  295
  296noun_plu(averages,average).
  297noun_plu(totals,total).
  298noun_plu(sums,sum).
  299noun_plu(degrees,degree).
  300noun_plu(sqmiles,sqmile).
  301noun_plu(ksqmiles,ksqmile).
  302noun_plu(million,million).
  303noun_plu(thousand,thousand).
  304noun_plu(times,time).
  305noun_plu(places,place).
  306noun_plu(areas,area).
  307noun_plu(capitals,capital).
  308noun_plu(cities,city).
  309noun_plu(continents,continent).
  310noun_plu(countries,country).
  311noun_plu(latitudes,latitude).
  312noun_plu(longitudes,longitude).
  313noun_plu(oceans,ocean).
  314noun_plu(persons,person).  noun_plu(people,person).
  315noun_plu(populations,population).
  316noun_plu(regions,region).
  317noun_plu(rivers,river).
  318noun_plu(seas,sea).
  319noun_plu(seamasses,seamass).
  320noun_plu(numbers,number).
  321
  322verb_root(border).
  323verb_root(contain).
  324verb_root(drain).
  325verb_root(exceed).
  326verb_root(flow).
  327verb_root(rise).
  328verb_root(govern).
  329
  330regular_pres(rise).
  331
  332verb_form(rises,rise,pres+fin,3+sg).
  333verb_form(rose,rise,past+fin,_).
  334verb_form(risen,rise,past+part,_).
  335
  336regular_pres(border).
  337
  338regular_past(bordered,border).
  339
  340verb_form(borders,border,pres+fin,3+sg).
  341verb_form(bordering,border,pres+part,_).
  342
  343regular_pres(contain).
  344
  345regular_past(contained,contain).
  346
  347verb_form(contains,contain,pres+fin,3+sg).
  348verb_form(containing,contain,pres+part,_).
  349
  350regular_pres(drain).
  351
  352regular_past(drained,drain).
  353
  354verb_form(drains,drain,pres+fin,3+sg).
  355verb_form(draining,drain,pres+part,_).
  356
  357regular_pres(govern).
  358
  359regular_past(governed,govern).
  360
  361verb_form(governs,govern,pres+fin,3+sg).
  362verb_form(governing,govern,pres+part,_).
  363
  364regular_pres(exceed).
  365
  366regular_past(exceeded,exceed).
  367
  368verb_form(exceeds,exceed,pres+fin,3+sg).
  369verb_form(exceeding,exceed,pres+part,_).
  370
  371verb_type(rise,main+intrans).
  372verb_type(border,main+trans).
  373verb_type(contain,main+trans).
  374verb_type(drain,main+intrans).
  375verb_type(exceed,main+trans).
  376verb_type(govern,main+trans).
  377
  378regular_pres(flow).
  379
  380regular_past(flowed,flow).
  381
  382verb_form(flows,flow,pres+fin,3+sg).
  383verb_form(flowing,flow,pres+part,_).
  384
  385verb_type(flow,main+intrans).
  386
  387adverb(yesterday).
  388adverb(tomorrow)