1% ===================================================================
    2% File 'parser_e2c.pl'
    3% Purpose: Attempto Controlled English to CycL conversions from SWI-Prolog  
    4% This implementation is an incomplete proxy for CycNL and likely will not work as well
    5% Maintainer: Douglas Miles
    6% Contact: $Author: dmiles $@users.sourceforge.net ;
    7% Version: 'parser_e2c.pl' 1.0.0
    8% Revision:  $Revision: 1.3 $
    9% Revised At:   $Date: 2002/06/06 15:43:15 $
   10% ===================================================================
   11
   12:- shared_parser_data(in_continent/2).   13
   14:- multifile(baseKB:expect_file_mpreds/1).   15:- dynamic(baseKB:expect_file_mpreds/1).   16% WHY DID I HAVE? :- prolog_load_context(file, File),(baseKB:expect_file_mpreds(File)->true;asserta(baseKB:expect_file_mpreds(File))).
   17:- set_prolog_flag(do_renames_sumo,never).   18
   19:- if(current_module(pfc)).   20:- install_constant_renamer_until_eof.   21:- endif.   22/*
   23
   24 _________________________________________________________________________
   25|	Copyright (C) 1982						  |
   26|									  |
   27|	David Warren,							  |
   28|		SRI International, 333 Ravenswood Ave., Menlo Park,	  |
   29|		California 94025, USA;					  |
   30|									  |
   31|	Fernando Pereira,						  |
   32|		Dept. of Architecture, University of Edinburgh,		  |
   33|		20 Chambers St., Edinburgh EH1 1JZ, Scotland		  |
   34|									  |
   35|	This program may be used, copied, altered or included in other	  |
   36|	programs only for academic purposes and provided that the	  |
   37|	authorship of the initial program is aknowledged.		  |
   38|	Use for commercial purposes without the previous written 	  |
   39|	agreement of the authors is forbidden.				  |
   40|_________________________________________________________________________|
   41
   42*/
   43:-discontiguous(verb_type_db_0/2).   44:-discontiguous(verb_root_db/1).   45:-discontiguous(verb_form_db/4).   46:-discontiguous(trans_LF/9).   47:-discontiguous(regular_pres_db/1).   48:-discontiguous(regular_past_db/2).   49:-discontiguous(noun_form_db/3).   50:-discontiguous(loc_pred_prep_db/3).   51
   52:- style_check(+discontiguous).   53:- style_check(-discontiguous).   54:- op(600,xfy,((--))).   55:- op(450,xfy,((:))).   56:- op(400,xfy,((&))).   57:- op(300,fx,(('`'))).   58:- op(200,xfx,((--))).   59
   60:- shared_parser_data((trans_LF/9)).   61
   62:- only_pfc(retractall(nldata_BRN_WSJ_LEXICON:text_bpos(the,nn))).   63
   64% :- begin_dynamic_reader.
   65:- asserta((t_l:enable_src_loop_checking)).   66
   67
   68deduce_subj_obj_LF(PropAttrib,Adj,Type,X,TypeY,Y,H):-
   69  subj_obj_LF(PropAttrib,Adj,Type,X,TypeY,Y,H).
   70
   71deduce_subject_LF(RS,Adj,Type,X,P):-subject_LF(RS,Adj,Type,X,P).
   72
   73verb_type_db(Verb,Type):-no_repeats(verb_type_db_0(Verb,Type)).
   74
   75txt_there_db(there,there).
   76
   77txt_not_db(not,not).
   78% txt_not_db(never,never).
   79
   80
   81
   82:- if(current_module(pfc)).   83:- must( \+ is_pfc_file).   
   84:- endif.   85
   86
   87
   88parser_chat80:txt_no_db(not,not).
   89txt_no_db(no,no).
   90
   91% :- listing(txt_no_db/2).
   92
   93
   94% =================================================================
   95% General Dictionary
   96% LEXICAL Data from newdic.pl
   97
   98terminator_db(.,_).
   99terminator_db(?,?).
  100terminator_db(!,!).
  101
  102% plt:-! ,fail.
  103plt:- t_l:usePlTalk,!.
  104plt2:- t_l:useAltPOS,!.
  105% plt:- t_l:chat80_interactive,!.
  106
  107loop_check_chat80(Call):-loop_check_chat80(Call,fail).
  108loop_check_chat80(Call,Else):-loop_check(Call,Else).
  109
  110not_violate(NotCCW,POS):-loop_check(not_violate0(NotCCW,POS)).
  111not_violate0(NotCCW,POS):-loop_check_chat80((ccw_db(NotCCW,CC)->CC=POS;true),fail).
  112
  113:-meta_predicate(plt_call(+,+,0)).  114:-meta_predicate(plt2_call(+,+,0)).  115% plt_call(Goal):-plt,!,no_repeats(Goal),dmsg(succeed_plt_call(Goal)).
  116plt_call(NotCCW,_POS,_Goal):-member(NotCCW,['?','river','borders']),!,fail.
  117plt_call(NotCCW,POS,Goal):-plt,!,loop_check_chat80(no_repeats(Goal)),not_violate(NotCCW,POS),must(once(not_violate(NotCCW,POS);(dmsg(succeed_plt_call(NotCCW,POS,Goal)),!,fail))).
  118plt2_call(NotCCW,_POS,_Goal):-member(NotCCW,['?','river','borders']),!,fail.
  119plt2_call(NotCCW,POS,Goal):-plt2,!,loop_check_chat80(no_repeats(Goal)),not_violate(NotCCW,POS),must(once(not_violate(NotCCW,POS);(dmsg(succeed_plt_call(NotCCW,POS,Goal)),!,fail))).
  120
  121
  122adverb_db(Quickly):-plt,talk_db(adv,Quickly),not_ccw(Quickly).
  123
  124conj_db(and).
  125conj_db(or).
  126conj_db(But):- cycQuery80(partOfSpeech(_,'CoordinatingConjunction',But)).
  127
  128int_pron_db(what,undef).
  129int_pron_db(which,undef).
  130int_pron_db(who,subj80).
  131int_pron_db(whom,compl).
  132
  133int_art_db(how,X,_,int_det(X)).
  134int_art_db(what,X,_,int_det(X)).
  135int_art_db(which,X,_,int_det(X)).
  136
  137det_db(the,No,the(No),def).
  138det_db(a,sg,a,indef).
  139det_db(an,sg,a,indef).
  140det_db(every,sg,every,indef).
  141det_db(some,_,some,indef).
  142det_db(any,_,any,indef).
  143det_db(all,pl,all,indef).
  144det_db(each,sg,each,indef).
  145det_db(no,_,no,indef).
  146
  147det_db(Det):-det_db(Det,_,_,_).
  148det_db(W):-det_db0(W), \+ (det_db(W,_,_,_)),dif(CCW,'Determiner'), \+ (ccw_db(W,CCW)).
  149det_db0(W):- (cycQuery80('determinerStrings'(_,W));cyckb_t('determinerStrings',_,W)),atom(W).
  150
  151number_db(W,I,Nb) :-
  152   tr_number(W,I),
  153   ag_number(I,Nb).
  154
  155tr_number(nquant(I),I).
  156tr_number(one,1).
  157tr_number(two,2).
  158tr_number(three,3).
  159tr_number(four,4).
  160tr_number(five,5).
  161tr_number(six,6).
  162tr_number(seven,7).
  163tr_number(eight,8).
  164tr_number(nine,9).
  165tr_number(ten,10).
  166
  167ag_number(1,sg).
  168ag_number(N,pl) :- N>1.
  169
  170quantifier_pron_db(everybody,every,person).
  171quantifier_pron_db(everyone,every,person).
  172quantifier_pron_db(everything,every,thing).
  173quantifier_pron_db(somebody,some,person).
  174quantifier_pron_db(someone,some,person).
  175quantifier_pron_db(something,some,thing).
  176quantifier_pron_db(anybody,any,person).
  177quantifier_pron_db(anyone,any,person).
  178quantifier_pron_db(anything,any,thing).
  179quantifier_pron_db(nobody,no,person).
  180quantifier_pron_db(nothing,no,thing).
  181
  182prep_db(as).
  183prep_db(at).
  184noun_plu_db(times,time).
  185%noun_plu_db(Liaisons, Liaison):- plt, lexicon_interface:noun_pl(Liaisons, Liaison, _Human).
  186adverb_db(yesterday).
  187adverb_db(tomorrow).
  188
  189prep_db(of).
  190prep_db(to).
  191prep_db(by).
  192prep_db(with).
  193prep_db(in).
  194prep_db(on).
  195prep_db(from).
  196prep_db(into).
  197prep_db(through).
  198prep_db(Above):-plt,talk_db(preposition,Above).
  199
  200noun_form_db(Plu,Sin,pl) :- noun_plu_db(Plu,Sin),not_ccw(Plu).
  201noun_form_db(Sin,Sin,sg) :- noun_sin_db(Sin),not_ccw(Sin).
  202
  203verb_form_db(V,V,inf,_) :- verb_root_db(V).
  204verb_form_db(V,V,pres+fin,Agmt) :-
  205   regular_pres_db(V),
  206   root_form_db(Agmt),
  207   verb_root_db(V).
  208verb_form_db(Past,Verb,past+_,_) :-
  209   regular_past_db(Past,Verb).
  210
  211root_form_db(1+sg).
  212root_form_db(2+_).
  213root_form_db(1+pl).
  214root_form_db(3+pl).
  215
  216verb_root_db(BE):-aux_verb_root_db(BE).
  217
  218
  219aux_verb_root_db(be).
  220aux_verb_root_db(have).
  221aux_verb_root_db(do).
  222   
  223verb_form_db(am,be,pres+fin,1+sg).
  224verb_form_db(are,be,pres+fin,2+sg).
  225verb_form_db((is),be,pres+fin,3+sg).
  226verb_form_db(are,be,pres+fin,_+pl).
  227verb_form_db(was,be,past+fin,1+sg).
  228verb_form_db(were,be,past+fin,2+sg).
  229verb_form_db(was,be,past+fin,3+sg).
  230verb_form_db(were,be,past+fin,_+pl).
  231verb_form_db(been,be,past+part,_).
  232verb_form_db(being,be,pres+part,_).
  233
  234verb_type_db_0(be,aux+be).
  235
  236regular_pres_db(have).
  237
  238regular_past_db(had,have).
  239
  240verb_form_db(has,have,pres+fin,3+sg).
  241verb_form_db(having,have,pres+part,_).
  242
  243verb_type_db_0(have,aux+have).
  244
  245regular_pres_db(do).
  246
  247verb_form_db(does,do,pres+fin,3+sg).
  248verb_form_db(did,do,past+fin,_).
  249verb_form_db(doing,do,pres+part,_).
  250verb_form_db(done,do,past+part,_).
  251
  252verb_type_db_0(do,aux+ditrans(_Prep)).
  253
  254% =================================================================
  255% PRONOUN DB
  256% =================================================================
  257pron_db(W):-rel_pron_db(W,_).
  258pron_db(W):-poss_pron_db(W,_,_,_).
  259pron_db(W):-pers_pron_db(W,_,_,_,_).
  260pron_db(W):-int_pron_db(W,_).
  261pron_db(W):-quantifier_pron_db(W,_,_).
  262
  263rel_pron_db(who,subj80).
  264rel_pron_db(whom,compl).
  265rel_pron_db(which,undef).
  266
  267poss_pron_db(my,_,1,sg).
  268poss_pron_db(your,_,2,_).
  269poss_pron_db(his,masc,3,sg).
  270poss_pron_db(her,fem,3,sg).
  271poss_pron_db(its,neut,3,sg).
  272poss_pron_db(our,_,1,pl).
  273poss_pron_db(their,_,3,pl).
  274
  275pers_pron_db(i,_,1,sg,subj80).
  276pers_pron_db(you,_,2,_,_).
  277pers_pron_db(he,masc,3,sg,subj80).
  278pers_pron_db(she,fem,3,sg,subj80).
  279pers_pron_db(it,neut,3,sg,_).
  280pers_pron_db(we,_,1,pl,subj80).
  281% dmiles added
  282pers_pron_db(they,_,3,pl,subj80).
  283% dmiles removed
  284% pers_pron_db(them,_,3,pl,subj80).
  285pers_pron_db(me,_,1,sg,compl(_)).
  286pers_pron_db(him,masc,3,sg,compl(_)).
  287pers_pron_db(her,fem,3,sg,compl(_)).
  288pers_pron_db(us,_,1,pl,compl(_)).
  289pers_pron_db(them,_,3,pl,compl(_)).
  290
  291
  292how_many_db([how,many]).
  293
  294pronoun_LF(_Argree2B,_C,_MoreIn,_X,_Y,_MoreOut,_PronounType):-fail.
  295pronoun_LF(Argree2B,FemMasc,MoreIn,X,Y,[adj(Argree2B)|MoreIn],typeOf(FemMasc,Argree2B,X,Y)):-!,fail,trace.
  296
  297% =================================================================
  298% PROPER INSTANCES OF
  299% =================================================================
  300% should inhereit from e2c
  301
  302meetsForm80(String,RootString,form80(MainPlusTrans,main+tv)):-!,fail,nop((String,RootString,form80(MainPlusTrans,main+tv))).
  303
  304noun_plu_db(places,place).
  305
  306noun_plu_db(P,S):-plt,talk_db(noun1,S,P).
  307noun_plu_db(continents,continent).
  308noun_plu_db(oceans,ocean).
  309noun_plu_db(regions,region).
  310noun_plu_db(rivers,river).
  311noun_plu_db(seas,sea).
  312noun_plu_db(seamasses,seamass).
  313
  314noun_plu_db(PluralString,SingularString):- meetsForm80(PluralString,SingularString,noun+plural).
  315noun_sin_db(Singular):- meetsForm80(Singular,Singular,noun+singular).
  316noun_sin_db(Singular):- noun_plu_db(_,Singular).
  317
  318noun_sin_db(InWord):- var(InWord),!,freeze(InWord,noun_sin_db(InWord)).
  319noun_sin_db(InWord):- var(InWord),!,freeze(InWord,noun_sin_db(InWord)).
  320
  321subject_LF(thing,continent,feature&place&continent,X,continent(X)).
  322subject_LF(thing,ocean,feature&place&seamass,X,ocean(X)).
  323subject_LF(thing,river,feature&river,X,river(X)).
  324subject_LF(thing,sea,feature&place&seamass,X,sea(X)).
  325subject_LF(thing,seamass,feature&place&seamass,X,seamass(X)).
  326subject_LF(thing,region,feature&place&_,X,region80(X)).
  327
  328
  329/* WHICH WHICH DENOTES A  */
  330
  331subject_LF(thing,place,feature&place&_,X,place(X)).
  332
  333/* WHICH EXISTENCE STEMS FROM A  */
  334
  335place(X) :- continent(X); region80(X); seamass(X); country(X).
  336
  337region80(R) :- in_continent(R,_).
  338
  339
  340continent(africa).
  341continent(america).
  342continent(antarctica).
  343continent(asia).
  344continent(australasia).
  345continent(europe).
  346
  347circle_of_latitude(equator).
  348circle_of_latitude(tropic_of_cancer).
  349circle_of_latitude(tropic_of_capricorn).
  350circle_of_latitude(arctic_circle).
  351circle_of_latitude(antarctic_circle).
  352
  353
  354seamass(X) :- ocean(X).
  355seamass(X) :- sea(X).
  356
  357ocean(arctic_ocean).
  358ocean(atlantic).
  359ocean(indian_ocean).
  360ocean(pacific).
  361ocean(southern_ocean).
  362
  363sea(baltic).
  364sea(black_sea).
  365sea(caspian).
  366sea(mediterranean).
  367sea(persian_gulf).
  368sea(red_sea).
  369
  370river(R) :- river_pathlist(R,_L).
  371
  372
  373
  374:- if(current_module(pfc)).  375==>(in_continent(north_america, america)).
  376:- else.  377:- dynamic(in_continent/2).  378in_continent(north_america, america).
  379:- endif.  380
  381% ------------------------------
  382% "Whoable Count Nouns" 
  383% ------------------------------
  384noun_plu_db(persons,person).  noun_plu_db(people,person).
  385subject_LF(thing,person,_,X,person(X)).
  386
  387
  388
  389
  390/* A CAPITOL (IS NOT _JUST_ A PLACE)  */
  391
  392
  393noun_plu_db(capitals,capital).
  394subject_LF(thing,capital,feature&city,X,capital(X)).
  395subj_obj_LF(property,capital,feature&city,X,feature&place&country,Y, capital(Y,X)).
  396capital(C,Cap) :- country(C,_,_,_,_,_,Cap,_).
  397capital(C) :- capital(_X,C).
  398
  399/* IS A SPECIALIZATION OF A CITY ... */
  400
  401noun_plu_db(cities,city).
  402subject_LF(thing,city,feature&city,X,city(X)).
  403
  404city(C) :- city(C,_,_).
  405:- show_shared_pred_info(city/1).  406
  407:- dynamic(city/3).  408city(tehran,iran,1010).
  409:- show_shared_pred_info(city/3).  410/* THAT INVOKES GOVERNING ACTIONS ... */
  411
  412trans_LF(govern,feature&_,X,feature&place&country,Y,capital(Y,X),[], _,_).
  413
  414:- show_shared_pred_info((trans_LF/9)).  415
  416verb_root_db(govern).
  417regular_pres_db(govern).
  418regular_past_db(governed,govern).
  419verb_form_db(governs,govern,pres+fin,3+sg).
  420verb_form_db(governing,govern,pres+part,_).
  421verb_type_db_0(govern,main+tv).
  422
  423/* UPON A COUNTRY */
  424
  425noun_plu_db(countries,country).
  426subject_LF(thing,country,feature&place&country,X,country(X)).
  427country(C) :- country(C,_,_,_,_,_,_,_).
  428country(iran,middle_east,33,-53,636363,32001000,tehran,rial).
  429
  430
  431% =================================================================
  432%  A PROPERTY IS SPECIALIZION OF A MPRED THAT IS PRESENT ON TYPE
  433% =================================================================
  434
  435
  436noun_plu_db(types,type).
  437subject_LF(thing,type,feature&type&_,X,tSet(X)).
  438noun_plu_db(formattypes,formattype).
  439noun_plu_db(datatypes,datatype).
  440subject_LF(thing,formattype,feature&formattype&_,X,ttFormatType(X)).
  441
  442noun_plu_db(TS,T):- noun_plu_db_via_types(TS,T).
  443
  444subject_LF(thing,Type,TYPEMASK,X,isa(X,Type)):- plt,loop_check_u(tSet(Type)),atom(Type),gen_typemask(Type,TYPEMASK).
  445subject_LF(restriction,Type,TYPEMASK,X,isa(X,Type)):- plt,loop_check_u(tSet(Type)),atom(Type),gen_typemask(Type,TYPEMASK).
  446
  447
  448gen_typemask(Type,measure&Type&_):- call_u(ttFormatType(Type)),!.
  449gen_typemask(Type,feature&Type&_).
  450gen_typemask(_,feature&_).
  451
  452
  453noun_plu_db_via_types(TS,T):- maybe_noun_or_adj(T),maybe_noun_or_adj(TS), (atom(TS)->atom_concat(T,'s',TS);true),loop_check_u(tSet(T)),atom(T),atom_concat(T,'s',TS).
  454maybe_noun_or_adj(T):- var(T)->true;(atom(T),not_ccw(T)).
  455
  456% 
  457% chat80("how many types are there?").
  458% chat80("what formattypes are types?").
  459
  460%  chat80("how are you?").
  461% test_chat80("you flow").
  462
  463test_chat80(U):- locally(t_l:chat80_interactive, must(chat80(U))).
  464
  465t10:- 
  466   test_chat80("how many postures are there?"),
  467   test_chat80("what are the postures?"),
  468   test_chat80("how many oceans are seas?"),
  469   test_chat80("how many oceans are seasmasses?"),
  470   test_chat80("how many types are there?"),
  471   test_chat80("how many formattypes are there?"),
  472   test_chat80("how many formattypes are there?"),
  473   !.
  474
  475/* A PROPERTY  */
  476
  477
  478noun_plu_db(properties,property).
  479subject_LF(thing,property,feature&mpred,X,isa_objectProperty(X)).
  480
  481subj_obj_LF(property,property,feature&mpred,X,feature&type&_,Y, hasPropertyOrValueISA(Y,X)).
  482
  483/* IS A SPECILIZATION OF A MPRED */
  484
  485noun_plu_db(mpreds,mpred).
  486subject_LF(thing,mpred,feature&mpred,X,mpred(X)).
  487
  488isa_objectProperty(P) :- hasProperty(_,P).
  489
  490hasPropertyOrValueISA(T,PorV):- (PorV=P;PorV=V), hasPropertyValueSVO(T,P,V),(PorV=P;PorV=V).
  491hasPropertyOrValueISA(T,PorV):- call_u(isa(PorV,T)).
  492
  493hasProperty(Type,P):-no_repeats((Type-P),hasPropertyValueSVO(Type,P,_)).
  494
  495hasPropertyValueSVO(SomeType,P,SomeVType):-call_u(mpred_arity(P,A)),A>=2, cycQuery80(argIsa(P,1,SomeType)),cycQuery80(argIsa(P,A,SomeVType)).
  496hasPropertyValueSVO(Type,P,Area) :- subj_obj_LF(property,Area,_Measure&Area,_X,feature&TYPELIST,_Y,Pred),deepestType(TYPELIST,Type),get_1st_order_functor(Pred,P),deepestType(TYPELIST,Type).
  497
  498get_1st_order_functor(Pred,P):- \+ (compound(Pred)),!,P=Pred.
  499get_1st_order_functor(Pred,P):-get_functor(Pred,F),(is_2nd_order_holds_maybe(F)->((arg(1,Pred,A),!,get_1st_order_functor(A,P)));P=F).
  500
  501:- if(current_module(pfc)).  502is_2nd_order_holds_maybe(F):- is_2nd_order_holds(F).
  503:- else.  504is_2nd_order_holds_maybe(_F):- fail.
  505:- endif.  506
  507/* THAT IS HAD */
  508/*
  509trans_LF(has,feature&mpred,X,feature&type,Y,hasProperty(Y,X),[], _,_).
  510verb_root_db(has).
  511regular_pres_db(has).
  512regular_past_db(had,has).
  513verb_form_db(has,has,pres+fin,3+sg).
  514verb_form_db(having,has,pres+part,_).
  515verb_type_db_0(has,main+tv).
  516*/
  517/* BY  SOME TYPE */
  518
  519
  520deepestType(TYPE,_):-var(TYPE),!,fail.
  521deepestType(TYPE&Next,Type):-var(Next),!,Type=TYPE.
  522deepestType(_&LIST,Type):-!,deepestType(LIST,Type).
  523deepestType(TYPE,Type):-Type=TYPE.
  524
  525typeAssignableTo(Type,SomeType):- call_u(transitive_subclass(Type,SomeType)).
  526typeAssignableTo(_Type,SomeType):- call_u(ttFormatType(SomeType)).
  527
  528
  529% TODO DECIDE IF UNEEDED hook:fact_always_true(isa(Type,type)):- clause(subject_LF(thing,Type,feature&_,_X,_),true).
  530% TODO DECIDE IF UNEEDED hook:fact_always_true(isa(Type,type)):- clause(subject_LF(restriction,Type,feature&_,_X,_),true).
  531
  532
  533type_allowed(feature&TYPEMASK,Type):-nonvar(TYPEMASK),!,type_allowed(TYPEMASK,Type),!.
  534type_allowed(TM,Type):-gen_typemask(Type,TM).
  535
  536type_allowed0(NV&TypeM,Type):-nonvar(NV),!,type_allowed(TypeM,Type).
  537type_allowed0(TypeM,Type):-Type==TypeM,!.
  538type_allowed0(TypeM&_,Type):- Type==TypeM,!.
  539
  540
  541
  542% =================================================================
  543% Having Referant Proper nouns
  544% =================================================================
  545:- shared_parser_data(name_template_db/2).  546name_db([black,sea],black_sea).
  547name_db([upper,volta],upper_volta).
  548name_db([Name],Name) :-
  549   name_template_db(Name,_), !.
  550%name_db([Name],Name) :- t_l:useAltPOS,downcase_atom(Name,DCName),loop_check( \+ (cw_db(DCName,_))).
  551
  552
  553name_template_db(X,feature&circle) :- circle_of_latitude(X).
  554
  555name_template_db(X,feature&city) :- city(X).
  556name_template_db(X,feature&place&continent) :- continent(X).
  557name_template_db(X,feature&place&country) :- country(X).
  558name_template_db(X,feature&place&_) :- region80(X).
  559name_template_db(X,feature&river) :- river(X).
  560name_template_db(X,feature&place&seamass) :- seamass(X).
  561
  562name_template_db(X,feature& ISA) :- plt,  nonvar(ISA), call_u(isa(X,ISA)).
  563name_template_db(X,feature& ISA & _) :- plt,  nonvar(ISA), call_u(isa(X,ISA)).
  564name_template_db(X,feature& _ & ISA ) :- plt,  nonvar(ISA), call_u(isa(X,ISA)).
  565
  566:- show_shared_pred_info(name_template_db/2).  567
  568% =================================================================
  569% FACETS (Adjectives) 
  570% =================================================================
  571
  572subject_LF(restriction,african,feature&_,X,african(X)).
  573subject_LF(restriction,american,feature&_,X,american(X)).
  574subject_LF(restriction,asian,feature&_,X,asian(X)).
  575subject_LF(restriction,european,feature&_,X,european(X)).
  576
  577african(X) :- in_ploc(X,africa).
  578american(X) :- in_ploc(X,america).
  579asian(X) :- in_ploc(X,asia).
  580european(X) :- in_ploc(X,europe).
  581
  582adj_db(african,restr).
  583adj_db(american,restr).
  584adj_db(asian,restr).
  585adj_db(european,restr).
  586
  587not_ccw(W):- \+ (ccw_db1(W,_)),!.
  588% closed class words
  589ccw_db(W,C):-no_repeats(ccw_db0(W,C);ccw_db3(W,C)).
  590ccw_db0(W,C):-one_must(ccw_db1(W,C),ccw_db2(W,C)).
  591ccw_db1(W,'Number-SP'):-no_repeats(W,number_db(W,_,_)).
  592ccw_db1(W,'Symbol-SP'):-no_repeats(W,terminator_db(W,_)).
  593ccw_db1(W,'Preposition'):-prep_db(W), \+ (ccw_db1(W,'Determiner')).
  594ccw_db1(W,'Pronoun'):-pron_db(W).
  595ccw_db1(W,'Conjunction'):-conj_db(W).
  596ccw_db1(W,'Determiner'):-det_db(W).
  597ccw_db1(W,'Conjunction'):-no_repeats(W,cycQuery80(partOfSpeech(_,'SubordinatingConjunction',W))).
  598ccw_db1(W,'Pronoun'):-no_repeats(W,cyckb_t('pronounStrings',_,W)).
  599ccw_db2(W,'Preposition'):-no_repeats(W,talk_db(preposition,W)).
  600ccw_db3(W,C):-ccw_db4(W,C), \+ (loop_check(adj_db(W,_))),not_ccw(W).
  601ccw_db4(W,'Verb'):-nonvar(W),verb_form_db(W,_,pres+_,_),!.
  602ccw_db4(W,'Verb'):-verb_form_db(W,_,pres+_,_).
  603
  604compatible_pos_db(_MostLikley,_Wanted).
  605
  606cw_db(W,C):-ccw_db(W,C).
  607cw_db(W,C):-nonvar(W),!,cw_db0(W,WC),!,C=WC.
  608cw_db(W,C):-cw_db0(W,C).
  609
  610cw_db0(W,C):-one_must(cw_db1(W,C),cw_db2(W,C)).
  611cw_db1(W,C):-ccw_db(W,C).
  612cw_db1(W,C):-ocw_db(W,C),dif(C,OC), \+ (ocw_db(W,OC)).
  613cw_db2(W,C):-one_must(ocw_db0(W,C),ocw_db1(W,C)).
  614
  615ocw_db(W,'Verb'):-no_repeats(W,(verb_form_db(W,_,_,_), \+ (ccw_db(W,CCW)),CCW\=W)).
  616ocw_db(W,C):-ocw_db0(W,C).
  617
  618ocw_db0(W,C):-one_must(ocw_db1(W,C),ocw_db3(W,C)).
  619ocw_db1(W,'Interjection'):-talk_db(interj,W).
  620ocw_db1(W,'Adverb'):-adverb_db(W),\+ ocw_db2(W,_).
  621ocw_db1(W,C):-ocw_db2(W,C),not_ccw(W).
  622ocw_db2(W,'Noun'):-noun_plu_db(W,_).
  623ocw_db2(W,'Adjective'):-adj_db(W,_).
  624ocw_db2(W,'Noun'):-noun_plu_db(_,W).
  625ocw_db3(W,SPOS):-  cycQuery80('suffixString'(CycWord,String)),String\='',atom_concat(_First,String,W),cycQuery80('derivationalAffixResultPOS'(CycWord,POS)),simplePOS(POS,SPOS).
  626
  627simplePOS(POS,SIMP):-call_u(posName(SIMP)),atom_concat(_,SIMP,POS).
  628
  629
  630subject_LF(restriction,AdjNounEan,feature&_,X,adjIsa(X,AdjNounEan)):- plt, adj_db(AdjNounEan,restr),not_ccw(AdjNounEan).
  631adjIsa(E,C):- only_pfc(call_u(isa_backchaing(E,C))),nonvar(C).
  632adj_db(AdjNounEan,restr):- plt,talk_db(adj,AdjNounEan),talk_db(noun1,AdjNounEan,_).
  633adj_db(AdjRestr,restr):-plt,talk_db(adj,AdjRestr), \+ (adj_db(AdjRestr,quant)), \+ (adverb_db(AdjRestr)).
  634adj_db(AdjRestr,restr):-meetsForm80(AdjRestr,AdjRestr,form80(adj+restr)).
  635
  636
  637verb_type_db_0(Verb,main+tv)  :-plt, trans_LF(Verb,_,_,_,_,_,_,_,_).
  638verb_type_db_0(Verb,main+iv):-plt,  intrans_LF(Verb,_,_,_,_,_).
  639verb_type_db_0(Verb,main+ditrans(_Prep)):- plt, ditrans_LF(Verb,_,_,_,_,_,_,_,_,_,_,_).
  640
  641verb_type_db_0(Verb,main+tv):- plt,   talk_db(transitive,Verb,_,_,_,_).
  642verb_type_db_0(Verb,main+iv):-plt,  talk_db(intransitive,Verb,_,_,_,_).
  643
  644:-style_check(-singleton).  645
  646verb_root_db(Govern):-plt,talk_db(_Verb_i,Govern,_Governs,_GovernedImperfect,_Governing,_Governed).
  647regular_pres_db(Govern):-plt,talk_db(_,Govern,_Governs,_GovernedImperfect,_Governing,_Governed).
  648regular_past_db(Governed,Govern):-plt,talk_db(_,Govern,_Governs,_GovernedImperfect,_Governing,Governed).
  649verb_form_db(Active,Verb,pres+part,_):-plt,talk_db(_,Verb,VerbPL,Imperfect,Active,PastPart).
  650verb_form_db(VerbPL,Verb,pres+fin,3+sg):-plt,talk_db(_,Verb,VerbPL,Imperfect,Active,PastPart).
  651verb_form_db(Imperfect,Verb,past+fin,_):-plt,talk_db(_,Verb,VerbPL,Imperfect,Active,PastPart).
  652verb_form_db(PastPart,Verb,past+part,_):-plt,talk_db(_,Verb,VerbPL,Imperfect,Active,PastPart).
  653
  654verb_root_db(Verb):-meetsForm80(Verb,Verb,form80(verb+root)).
  655verb_root_db(Verb):-meetsForm80(Verb,Verb,form80(3+sg)).
  656verb_type_db_0(Verb,MainPlusTrans):-verb_root_db(Verb),meetsForm80(_Form,Verb,form80(MainPlusTrans,main+tv)).
  657regular_pres_db(Verb):- meetsForm80(Verb,Verb,form80(regular_pres)).
  658regular_past_db(Form,Verb):- meetsForm80(Form,Verb,form80(regular_past)).
  659verb_form_db(Form,Verb,AsPresFin,As3_plus_sin):- meetsForm80(Form,Verb,form80(AsPresFin,pres+fin)), meetsForm80(Verb,Verb,form80(As3_plus_sin,3+sg)).
  660verb_form_db(Form,Verb,TensePlusPart,_):- meetsForm80(Form,Verb,form80(TensePlusPart)).
  661regular_pres_db(Verb):- verb_root_db(Verb).
  662
  663:-style_check(+singleton).  664
  665
  666
  667verb_root_db(border).
  668regular_pres_db(border).
  669regular_past_db(bordered,border).
  670verb_form_db(borders,border,pres+fin,3+sg).
  671verb_form_db(bordering,border,pres+part,_).
  672verb_type_db_0(border,main+tv).
  673trans_LF(border, feature&place&_,X,feature&place&_,Y,borders(X,Y),[], _,_).
  674
  675borders(X,C) :- var(X), nonvar(C), !, borders(C,X).
  676borders(afghanistan,iran).
  677borders(iran,afghanistan).
  678
  679
  680/* THAT HAS COUNTABLE ATTRIBUTES SUCH AS.. */
  681
  682subject_LF(thing,longitude,measure&position,X,longitude80(X)).
  683subject_LF(thing,latitude,measure&position,X,latitude80(X)).
  684subj_obj_LF(property,longitude,measure&position,X,feature&_,Y,longitude80(Y,X)).
  685subj_obj_LF(property,latitude, measure&position,X,feature&_,Y,latitude80(Y,X)).
  686noun_plu_db(longitudes,longitude). noun_plu_db(latitudes,latitude).
  687
  688longitude80(C,L--degrees) :- country(C,_,_,L,_,_,_,_).
  689latitude80(C,L--degrees) :- country(C,_,L,_,_,_,_,_).
  690
  691longitude80(_X--degrees).
  692latitude80(_X--degrees).
  693
  694latitude80(tropic_of_capricorn,-23--degrees).
  695latitude80(tropic_of_cancer,23--degrees).
  696latitude80(equator,0--degrees).
  697latitude80(arctic_circle,67--degrees).
  698latitude80(antarctic_circle,-67--degrees).
  699
  700
  701% ------------------------------
  702% "N/S/E/W/of" 
  703% ------------------------------
  704loc_pred_prep_db(east,prep(eastof),of).
  705loc_pred_prep_db(west,prep(westof),of).
  706loc_pred_prep_db(north,prep(northof),of).
  707loc_pred_prep_db(south,prep(southof),of).
  708
  709adjunction_lf(eastof,feature&_-X,feature&_-Y,eastof(X,Y)).
  710adjunction_lf(westof,feature&_-X,feature&_-Y,westof(X,Y)).
  711adjunction_lf(northof,feature&_-X,feature&_-Y,northof(X,Y)).
  712adjunction_lf(southof,feature&_-X,feature&_-Y,southof(X,Y)).
  713
  714eastof(X1,X2) :- longitude80(X1,L1), longitude80(X2,L2), exceeds(L2,L1).
  715northof(X1,X2) :- latitude80(X1,L1), latitude80(X2,L2), exceeds(L1,L2).
  716southof(X1,X2) :- latitude80(X1,L1), latitude80(X2,L2), exceeds(L2,L1).
  717westof(X1,X2) :- longitude80(X1,L1), longitude80(X2,L2), exceeds(L1,L2).
  718
  719
  720
  721% ------------------------------
  722% "Population is having a quantitity"
  723% ------------------------------
  724noun_plu_db(populations,population).
  725
  726subject_LF(thing,population,measure&countables,X,population(X)).
  727
  728subj_obj_LF(property,population, measure&countables,X,feature&_,Y,population(Y,X)).
  729
  730population(C,P--thousand) :- city(C,_,P).
  731population(C,P--million) :- country(C,_,_,_,_,P0,_,_), P is integer(P0/1.0E6).
  732
  733population(_X--million).
  734population(_X--thousand).
  735
  736measure_unit_type_db(thousand,measure&countables,[],thousand).
  737measure_unit_type_db(million,measure&countables,[],million).
  738
  739% ------------------------------
  740/*
  741
  742 % BREAKS THINGS?
  743
  744noun_sin_db(QuantProp):- quantity_props_db(_OfType,QuantProp).
  745
  746subject_LF(thing,QuantProp,measure&OfType,X,denotesQuantity(X,OfType)):- quantity_props_db(OfType,QuantProp).
  747subj_obj_LF(property,QuantProp, measure&OfType,X,feature&_,Y,holds_t(QuantProp,Y,X)):- quantity_props_db(OfType,QuantProp).
  748
  749quantity_props_db(inches,height).
  750
  751denotesQuantity(_X--million,Countables):-quantity_props_db(Countables,_).
  752denotesQuantity(_X--thousand,Countables):-quantity_props_db(Countables,_).
  753denotesQuantity(N, Countables):-number(N),quantity_props_db(Countables,_).
  754*/
  755
  756
  757% ------------------------------
  758% "Contains" Inversion of the 'in' relation.
  759% ------------------------------
  760verb_root_db(contain).
  761verb_type_db_0(contain,main+tv).
  762regular_pres_db(contain).
  763regular_past_db(contained,contain).
  764verb_form_db(contains,contain,pres+fin,3+sg).
  765verb_form_db(containing,contain,pres+part,_).
  766trans_LF(contain,feature&place&_,X,feature&_,Y,in_ploc(Y,X),[], _,_).
  767
  768contains80(X,Y) :- contains0(X,Y).
  769contains80(X,Y) :- contains0(X,W), contains80(W,Y).
  770
  771contains0(america,north_america).
  772
  773
  774% ------------------------------
  775% "In" 
  776% ------------------------------
  777context_pron_db(in,place,where).
  778context_pron_db(at,time,when).
  779% TODO context_pron_db(for,reason,why).
  780% TODO context_pron_db(by,method,how).
  781
  782adjunction_lf(in,feature&_-X,feature&place&_-Y,in_ploc(X,Y)).
  783
  784:- share_mp(in_ploc/2).  785in_ploc(X,Y) :- var(X), nonvar(Y), !, contains80(Y,X).
  786in_ploc(X,Y) :- in_01(X,W), ( W=Y ; in_ploc(W,Y) ).
  787
  788in_01(X,Y) :- in_continent(X,Y).
  789in_01(X,Y) :- city(X,Y,_).
  790in_01(X,Y) :- country(X,Y,_,_,_,_,_,_).
  791in_01(X,Y) :- flows(X,Y).
  792
  793in_continent(middle_east,  asia).
  794
  795
  796
  797
  798% =================================================================
  799% INTERACTION OF TYPES
  800% =================================================================
  801
  802
  803
  804/* Verbs */
  805
  806verb_root_db(rise).
  807regular_pres_db(rise).
  808verb_form_db(rises,rise,pres+fin,3+sg).
  809verb_form_db(rose,rise,past+fin,_).
  810verb_form_db(risen,rise,past+part,_).
  811verb_type_db_0(rise,main+iv).
  812intrans_LF(rise,feature&river,X,rises(X,Y), [slot(prep(in),feature&place&_,Y,_,free)],_).
  813
  814rises(R,C) :- river_pathlist(R,L), last(L,C).
  815
  816
  817verb_root_db(drain).
  818regular_pres_db(drain).
  819regular_past_db(drained,drain).
  820verb_form_db(drains,drain,pres+fin,3+sg).
  821verb_form_db(draining,drain,pres+part,_).
  822verb_type_db_0(drain,main+iv).
  823intrans_LF(drain,feature&river,X,drains(X,Y), [slot(prep(into),feature&place&_,Y,_,free)],_).
  824
  825drains(R,S) :- river_pathlist(R,L), lists_first(L,S).
  826
  827lists_first([F|_],F).
  828
  829verb_root_db(flow).
  830regular_pres_db(flow).
  831regular_past_db(flowed,flow).
  832verb_form_db(flows,flow,pres+fin,3+sg).
  833verb_form_db(flowing,flow,pres+part,_).
  834verb_type_db_0(flow,main+iv).
  835intrans_LF(flow,feature&river,X,flows(X,Y), [slot(prep(through),feature&place&_,Y,_,free)],_).
  836intrans_LF(flow,feature&river,X,flows(X,Y,Z), [slot(prep(into),feature&place&_,Z,_,free), slot(prep(from),feature&place&_,Y,_,free)],_). 
  837
  838flows(R,C) :- flows(R,C,_).
  839flows(R,C1,C2) :- river_pathlist(R,L), flow_links(L,C2,C1).
  840flow_links([X1,X2|_],X1,X2).
  841flow_links([_|L],X1,X2) :- flow_links(L,X1,X2).
  842
  843
  844
  845% ------------------------------
  846/* Measure of Mass Nouns*/
  847% ------------------------------
  848
  849noun_plu_db(areas,area).
  850subject_LF(thing,area,measure&area,X,isa_area(X)).
  851subj_obj_LF(property,area,measure&area,X,feature&place&_,Y,areaOf(Y,X)).
  852areaOf(C,A--ksqmiles) :- country(C,_,_,_,A0,_,_,_), A is A0/1000.
  853isa_area(_X--ksqmiles).
  854
  855
  856measure_unit_type_db(sqmile,measure&area,[],sqmiles).
  857measure_unit_type_db(ksqmile,measure&area,[],ksqmiles).
  858
  859ratio_db(sqmiles,ksqmiles,1,1000).
  860ratio_db(ksqmiles,sqmiles,1000,1).
  861noun_plu_db(ksqmiles,ksqmile).
  862noun_plu_db(sqmiles,sqmile).
  863
  864/*
  865
  866property_measured_in_db(area,sqmile,sqmiles).
  867+
  868subj_obj_LF(property,area,measure&area,X,feature&place&_,Y,areaOf(Y,X)).
  869
  870->
  871
  872noun_plu_db(areas,area).
  873subject_LF(thing,area,measure&area,X,isa_area(X)).
  874subj_obj_LF(property,area,measure&area,X,feature&place&_,Y,areaOf(Y,X)).
  875areaOf(C,A--ksqmiles) :- country(C,_,_,_,A0,_,_,_), A is integer(A0/1000).
  876isa_area(_X--ksqmiles).
  877
  878
  879measure_unit_type_db(sqmile,measure&area,[],sqmiles).
  880measure_unit_type_db(ksqmile,measure&area,[],ksqmiles).
  881
  882ratio_db(sqmiles,ksqmiles,1,1000).
  883ratio_db(ksqmiles,sqmiles,1000,1).
  884noun_plu_db(ksqmiles,ksqmile).
  885noun_plu_db(sqmiles,sqmile).
  886
  887
  888*/
  889:- shared_parser_data(clex_iface:clex_noun/5).  890
  891subject_LF(thing,CountNoun,feature&_,X,isa(X,RootNoun)):-  plt, clex_noun(CountNoun, RootNoun,_,_,_), \+ (ratio_db(RootNoun,_,_,_)).
  892subject_LF(thing,CountNoun,feature&_,X,adjIsa2(X,RootNoun)):- plt, clex_adj(CountNoun, RootNoun,_), \+ (ratio_db(RootNoun,_,_,_)).
  893
  894
  895
  896/* Measure of Proportions and the like */
  897noun_form_db(proportion,proportion,_).
  898comparator_db(proportion,_,V,[],proportion(V)).
  899noun_plu_db(degrees,degree).
  900measure_unit_type_db(degree,measure&position,[],degrees).
  901comparator_db(percentage,_,V,[],proportion(V)).
  902noun_form_db(percentage,percentage,_).
  903noun_plu_db(thousand,thousand).
  904noun_plu_db(million,million).
  905ratio_db(million,thousand,1000,1).
  906ratio_db(thousand,million,1,1000).
  907
  908
  909adj_db(average,restr).
  910aggr_adj_db(average,_,_,average).
  911noun_plu_db(averages,average).
  912aggr_noun_db(average,_,_,average).
  913
  914
  915aggr_adj_db(minimum,_,_,minimum).
  916adj_db(minimum,restr).
  917aggr_adj_db(maximum,_,_,maximum).
  918adj_db(maximum,restr).
  919
  920meta_noun_db(number,_,V,feature&_,X,P,numberof(X,P,V)).
  921noun_plu_db(numbers,number).
  922
  923
  924adj_db(total,restr).
  925noun_plu_db(totals,total).
  926aggr_adj_db(total,_,_,total).
  927aggr_noun_db(total,_,_,total).
  928aggr_noun_db(sum,_,_,total).
  929noun_plu_db(sums,sum).
  930
  931
  932/* Measure of Greater or Lesser amounts*/
  933verb_root_db(exceed).
  934verb_type_db_0(exceed,main+tv).
  935regular_pres_db(exceed).
  936regular_past_db(exceeded,exceed).
  937verb_form_db(exceeds,exceed,pres+fin,3+sg).
  938verb_form_db(exceeding,exceed,pres+part,_).
  939trans_LF(exceed,measure&Type,X,measure&Type,Y,exceeds(X,Y),[], _,_).
  940subj_obj_LF(attribute,great,measure&Type,X,measure&Type,Y,exceeds(X,Y)).
  941
  942
  943measure_op_db(id(_Why),X,X,true).
  944measure_op_db(same,X,Y,X=Y).
  945measure_op_db(less,X,Y,exceeds(Y,X)).
  946measure_op_db('not'(_Why)+less,X,Y,\+exceeds(Y,X)).
  947measure_op_db(more,X,Y,exceeds(X,Y)).
  948measure_op_db('not'(_Why)+more,X,Y,\+exceeds(X,Y)).
  949
  950inverse_db(most,-,least).
  951inverse_db(least,-,most).
  952inverse_db(same,-,same).
  953inverse_db(less,-,more).
  954inverse_db(more,-,less).
  955inverse_db(X,+,X).
  956
  957exceeds(X--U,Y--U) :- !, X > Y.
  958exceeds(X1--U1,X2--U2) :- ratio_db(U1,U2,M1,M2), X1*M1 > X2*M2.
  959
  960sup_adj_db(Biggest,Big):-plt,talk_db(superl,Big,Biggest).
  961
  962
  963% /* Comparative */
  964rel_adj_db(Bigger,Big):-plt,talk_db(comp,Big,Bigger).
  965subj_obj_LF(attribute,small,feature&place&_,X,measure&area,Y,areaOf(X,Y)).
  966subj_obj_LF(attribute,large,feature&place&_,X,measure&area,Y,areaOf(X,Y)).
  967
  968subj_obj_LF(attribute,small,feature&Place&_,X,measure&Area,Y,holds_t(AreaPred,X,Y)):-type_measured_by_pred_db(Place,Area,AreaPred).
  969subj_obj_LF(attribute,large,feature&Place&_,X,measure&Area,Y,holds_t(AreaPred,X,Y)):-type_measured_by_pred_db(Place,Area,AreaPred).
  970
  971type_measured_by_pred_db(human,feet,height).
  972
  973units_db(small,measure&_).
  974units_db(large,measure&_).
  975rel_adj_db(smaller,small).
  976sup_adj_db(smallest,small).
  977rel_adj_db(larger,large).
  978sup_adj_db(largest,large).
  979adj_sign_db(large,+).
  980adj_sign_db(small,-).
  981adj_sign_db(great,+).
  982
  983
  984comp_adv_db(less).
  985comp_adv_db(more).
  986
  987sup_adv_db(least).
  988sup_adv_db(most).
  989
  990rel_adj_db(less,small).
  991rel_adj_db(greater,great).
  992
  993
  994rel_adj_db(bigger,big).
  995sup_adj_db(biggest,big).
  996adj_db(small,quant).
  997adj_db(large,quant).
  998adj_db(great,quant).
  999adj_db(big,quant).
 1000
 1001adj_db(Big,quant):-plt,talk_db(superl,Big,_Biggest).
 1002adj_db(Big,quant):-plt,talk_db(comp,Big,_Bigger).
 1003
 1004adj_db(old,quant).
 1005adj_db(new,quant).
 1006rel_adj_db(older,old).
 1007sup_adj_db(oldest,old).
 1008rel_adj_db(newer,new).
 1009sup_adj_db(newest,new).
 1010
 1011
 1012
 1013/*
 1014We can parse:
 1015
 1016which is the largest X?
 1017
 1018but also need to parse:
 1019
 1020which X is the largest?
 1021
 1022
 1023chat80 what are the items?
 1024chat80 how many items are there?
 1025chat80 how many types are there?
 1026chat80 how many postures are there?
 1027chat80("what are the postures that are verbs?")
 1028chat80("how many rivers are rivers?").
 1029chat80 you flow to the ocean
 1030*/
 1031
 1032
 1033current_dcg_predicate(F/A):-current_predicate(F/A).
 1034
 1035toDCPred(Type,Pred,In,Out):-compound(Type),!,functor(Type,F,A),A2 is A + 2,current_dcg_predicate(F/A2),
 1036   once((length(Args,A),Type=..[F|Args],append(Args,[In,Out],Dargs))),Pred=..[F|Dargs].
 1037
 1038toDCPred(Type,Pred,In,Out):- current_dcg_predicate(F/A2),A is A2 - 2,
 1039   once((length(Args,A),Type=..[F|Args],append(Args,[In,Out],Dargs))),Pred=..[F|Dargs].
 1040
 1041probeDCG(Left,Content,Right,Type):-length_between(0,1,Left),length_between(0,1,Right),append(Left,Content,First),append(First,Right,In),
 1042  toDCPred(Type,Pred,In,[]),Pred.
 1043:-share_mp(ph/2). 1044ph(Type,Content):-show_call(probeDCG(_,Content,_,Type)).
 1045
 1046length_between(S,E,Left):-between(S,E,X),length(Left,X).
 1047
 1048
 1049:-share_mp(must_test_801/3). 1050
 1051must_test_801([which, are, the, largest, african, countries, ?], [ parse(whq(feature&place&country-B, s(np(3+sg, wh(feature&place&country-B), []), verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(det(the(sg)), [sup(most, adj(large)), adj(african)], country), []))], []))), sem((answer80([A]):-B^ (setof(C:D, (country(D), area(D, C), african(D)), B), aggregate80(max, B, A)))), qplan((answer80([D]):-C^ (setof(B:A, (african(A), {country(A)}, area(A, B)), C), aggregate80(max, C, D)))), 
 1052answers([sudan])],[time(0.0)]).
 1053must_test_801([what, rivers, are, there, ?], [sent([what, rivers, are, there, ?]), parse(whq(feature&river-B, s(np(3+pl, np_head(int_det(feature&river-B), [], river), []), verb(be, active, pres+fin, [], pos(_)), [void(_Why)], []))), sem((answer80([A]):-river(A), A^true)), qplan((answer80([B]):-river(B), B^true)), 
 1054answers([amazon, amu_darya, amur, brahmaputra, colorado, congo_river, cubango, danube, don, elbe, euphrates, ganges, hwang_ho, indus, irrawaddy, lena, limpopo, mackenzie, mekong, mississippi, murray, niger_river, nile, ob, oder, orange, orinoco, parana, rhine, rhone, rio_grande, salween, senegal_river, tagus, vistula, volga, volta, yangtze, yenisei, yukon, zambesi])],[time(0.0)]).
 1055must_test_801([does, afghanistan, border, china, ?], [sent([does, afghanistan, border, china, ?]), parse(q(s(np(3+sg, nameOf(afghanistan), []), verb(border, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, name(china), []))], []))), sem((answer80([]):-borders(afghanistan, china))), qplan((answer80([]):-{borders(afghanistan, china)})), 
 1056answers([true])],[time(0.0)]).
 1057must_test_801([what, is, the, capital, of, upper_volta, ?], [sent([what, is, the, capital, of, upper_volta, ?]), parse(whq(feature&city-B, s(np(3+sg, wh(feature&city-B), []), verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(det(the(sg)), [], capital), [pp(prep(of), np(3+sg, name(upper_volta), []))]))], []))), sem((answer80([A]):-capital(upper_volta, A))), qplan((answer80([A]):-capital(upper_volta, A))), 
 1058answers([ouagadougou])],[time(0.0010000000000000009)]).
 1059must_test_801([where, is, the, largest, country, ?], [sent([where, is, the, largest, country, ?]), parse(whq(feature&place&A-B, s(np(3+sg, np_head(det(the(sg)), [sup(most, adj(large))], country), []), verb(be, active, pres+fin, [], pos(_)), [varg(pred, pp(prep(in), np(_, np_head(int_det(feature&place&A-B), [], place), [])))], []))), sem((answer80([A]):-B^ (C^ (setof(D:E, (country(E), area(E, D)), C), aggregate80(max, C, B)), place(A), in_ploc(B, A)))), qplan((answer80([F]):-E^D^ (setof(C:B, (country(B), area(B, C)), D), aggregate80(max, D, E), in_ploc(E, F), {place(F)}))), 
 1060answers([asia, northern_asia])],[time(0.0009999999999999731)]).
 1061must_test_801([which, countries, are, european, ?], [sent([which, countries, are, european, ?]), parse(whq(feature&place&country-B, s(np(3+pl, np_head(int_det(feature&place&country-B), [], country), []), verb(be, active, pres+fin, [], pos(_)), [varg(pred, adj(european))], []))), sem((answer80([A]):-country(A), european(A))), qplan((answer80([A]):-european(A), {country(A)})), 
 1062answers([albania, andorra, austria, belgium, bulgaria, cyprus, czechoslovakia, denmark, east_germany, eire, finland, france, greece, hungary, iceland, italy, liechtenstein, luxembourg, malta, monaco, netherlands, norway, poland, portugal, romania, san_marino, spain, sweden, switzerland, united_kingdom, west_germany, yugoslavia])],[time(0.0)]).
 1063must_test_801([which, is, the, largest, african, country, ?], [sent([which, is, the, largest, african, country, ?]), parse(whq(feature&place&country-B, s(np(3+sg, wh(feature&place&country-B), []), verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(det(the(sg)), [sup(most, adj(large)), adj(african)], country), []))], []))), sem((answer80([A]):-B^ (setof(C:D, (country(D), area(D, C), african(D)), B), aggregate80(max, B, A)))), qplan((answer80([D]):-C^ (setof(B:A, (african(A), {country(A)}, area(A, B)), C), aggregate80(max, C, D)))), 
 1064answers([sudan])],[time(0.0)]).
 1065must_test_801([what, is, the, ocean, that, borders, african, countries, and, that, borders, asian, countries, ?], [sent([what, is, the, ocean, that, borders, african, countries, and, that, borders, asian, countries, ?]), parse(whq(feature&place&seamass-B, s(np(3+sg, wh(feature&place&seamass-B), []), verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(det(the(sg)), [], ocean), [conj(and, rel(feature&place&seamass-C, s(np(3+sg, wh(feature&place&seamass-C), []), verb(border, active, pres+fin, [], pos(_)), [varg(dir, np(3+pl, np_head(generic, [adj(african)], country), []))], [])), rel(feature&place&seamass-C, s(np(3+sg, wh(feature&place&seamass-C), []), verb(border, active, pres+fin, [], pos(_)), [varg(dir, np(3+pl, np_head(generic, [adj(asian)], country), []))], [])))]))], []))), sem((answer80([A]):-ocean(A), B^ (country(B), african(B), borders(A, B)), C^ (country(C), asian(C), borders(A, C)))), qplan((answer80([A]):-B^C^ (ocean(A), {borders(A, B), {african(B)}, {country(B)}}, {borders(A, C), {asian(C)}, {country(C)}}))), 
 1066answers([indian_ocean])],[time(0.0020000000000000018)]).
 1067must_test_801([what, are, the, capitals, of, the, countries, bordering, the, baltic, ?], [sent([what, are, the, capitals, of, the, countries, bordering, the, baltic, ?]), parse(whq(feature&city-B, s(np(3+pl, wh(feature&city-B), []), verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+pl, np_head(det(the(pl)), [], capital), [pp(prep(of), np(3+pl, np_head(det(the(pl)), [], country), [reduced_rel(feature&place&country-D, s(np(3+pl, wh(feature&place&country-D), []), verb(border, active, inf, [prog], pos(_)), [varg(dir, np(3+sg, name(baltic), []))], []))]))]))], []))), sem((answer80([D]):-setof([A]:C, (country(A), borders(A, baltic), setof(B, capital(A, B), C)), D))), qplan((answer80([H]):-setof([E]:G, (country(E), borders(E, baltic), setof(F, capital(E, F), G)), H))), 
 1068answers([[[denmark]:[copenhagen], [east_germany]:[east_berlin], [finland]:[helsinki], [poland]:[warsaw], [soviet_union]:[moscow], [sweden]:[stockholm], [west_germany]:[bonn]]])],[time(0.0010000000000000009)]).
 1069must_test_801([how, many, countries, does, the, danube, flow, through, ?], [sent([how, many, countries, does, the, danube, flow, through, ?]), parse(whq(feature&place&country-B, s(np(3+sg, nameOf(danube), []), verb(flow, active, pres+fin, [], pos(_)), [], [pp(prep(through), np(3+pl, np_head(quant(same, wh(feature&place&country-B)), [], country), []))]))), sem((answer80([A]):-numberof(B, (country(B), flows(danube, B)), A))), qplan((answer80([B]):-numberof(A, (flows(danube, A), {country(A)}), B))), 
 1070answers([6])],[time(0.0010000000000000009)]).
 1071must_test_801([what, is, the, average, area, of, the, countries, in, each, continent, ?], [sent([what, is, the, average, area, of, the, countries, in, each, continent, ?]), parse(whq(A-C, s(np(3+sg, wh(A-C), []), verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(det(the(sg)), [adj(average)], area), [pp(prep(of), np(3+pl, np_head(det(the(pl)), [], country), [pp(prep(in), np(3+sg, np_head(det(each), [], continent), []))]))]))], []))), sem((answer80([B, E]):-continent(B), [ (0--ksqmiles):[andorra], (0--ksqmiles):[liechtenstein], (0--ksqmiles):[malta], (0--ksqmiles):[monaco], (0--ksqmiles):[san_marino], (1--ksqmiles):[luxembourg], (4--ksqmiles):[cyprus], (11--ksqmiles):[albania], (12--ksqmiles):[belgium], (14--ksqmiles):[netherlands], (16--ksqmiles):[switzerland], (17--ksqmiles):[denmark], (27--ksqmiles):[eire], (32--ksqmiles):[austria], (35--ksqmiles):[portugal], (36--ksqmiles):[hungary], (40--ksqmiles):[iceland], (41--ksqmiles):[east_germany], (43--ksqmiles):[bulgaria], (49--ksqmiles):[czechoslovakia], (51--ksqmiles):[greece], (92--ksqmiles):[romania], (94--ksqmiles):[united_kingdom], (96--ksqmiles):[west_germany], (99--ksqmiles):[yugoslavia], (116--ksqmiles):[italy], (120--ksqmiles):[poland], (125--ksqmiles):[norway], (130--ksqmiles):[finland], (174--ksqmiles):[sweden], (195--ksqmiles):[spain], (213--ksqmiles):[france]]^ (setof(D:[C], (area(C, D), country(C), in_ploc(C, B)), [ (0--ksqmiles):[andorra], (0--ksqmiles):[liechtenstein], (0--ksqmiles):[malta], (0--ksqmiles):[monaco], (0--ksqmiles):[san_marino], (1--ksqmiles):[luxembourg], (4--ksqmiles):[cyprus], (11--ksqmiles):[albania], (12--ksqmiles):[belgium], (14--ksqmiles):[netherlands], (16--ksqmiles):[switzerland], (17--ksqmiles):[denmark], (27--ksqmiles):[eire], (32--ksqmiles):[austria], (35--ksqmiles):[portugal], (36--ksqmiles):[hungary], (40--ksqmiles):[iceland], (41--ksqmiles):[east_germany], (43--ksqmiles):[bulgaria], (49--ksqmiles):[czechoslovakia], (51--ksqmiles):[greece], (92--ksqmiles):[romania], (94--ksqmiles):[united_kingdom], (96--ksqmiles):[west_germany], (99--ksqmiles):[yugoslavia], (116--ksqmiles):[italy], (120--ksqmiles):[poland], (125--ksqmiles):[norway], (130--ksqmiles):[finland], (174--ksqmiles):[sweden], (195--ksqmiles):[spain], (213--ksqmiles):[france]]), aggregate80(average, [ (0--ksqmiles):[andorra], (0--ksqmiles):[liechtenstein], (0--ksqmiles):[malta], (0--ksqmiles):[monaco], (0--ksqmiles):[san_marino], (1--ksqmiles):[luxembourg], (4--ksqmiles):[cyprus], (11--ksqmiles):[albania], (12--ksqmiles):[belgium], (14--ksqmiles):[netherlands], (16--ksqmiles):[switzerland], (17--ksqmiles):[denmark], (27--ksqmiles):[eire], (32--ksqmiles):[austria], (35--ksqmiles):[portugal], (36--ksqmiles):[hungary], (40--ksqmiles):[iceland], (41--ksqmiles):[east_germany], (43--ksqmiles):[bulgaria], (49--ksqmiles):[czechoslovakia], (51--ksqmiles):[greece], (92--ksqmiles):[romania], (94--ksqmiles):[united_kingdom], (96--ksqmiles):[west_germany], (99--ksqmiles):[yugoslavia], (116--ksqmiles):[italy], (120--ksqmiles):[poland], (125--ksqmiles):[norway], (130--ksqmiles):[finland], (174--ksqmiles):[sweden], (195--ksqmiles):[spain], (213--ksqmiles):[france]], E)))), qplan((answer80([F, J]):-continent(F), I^ (setof(H:[G], (area(G, H), country(G), in_ploc(G, F)), I), aggregate80(average, I, J)))), 
 1072answers([[europe, 58.84375--ksqmiles]])],[time(0.0040000000000000036)]).
 1073must_test_801([is, there, more, than, one, country, in, each, continent, ?], [sent([is, there, more, than, one, country, in, each, continent, ?]), parse(q(s(there, verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(quant(more, nquant(1)), [], country), [pp(prep(in), np(3+sg, np_head(det(each), [], continent), []))]))], []))), sem((answer80([]):- \+A^ (continent(A), \+C^ (numberof(B, (country(B), in_ploc(B, A)), C), C>1)))), qplan((answer80([]):- \+D^ (continent(D), \+F^ (numberof(E, (country(E), in_ploc(E, D)), F), F>1)))), 
 1074answers([false])],[time(0.0010000000000000009)]).
 1075must_test_801([is, there, some, ocean, that, does, not, border, any, country, ?], [sent([is, there, some, ocean, that, does, not, border, any, country, ?]), parse(q(s(there, verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(det(some), [], ocean), [rel(feature&place&seamass-B, s(np(3+sg, wh(feature&place&seamass-B), []), verb(border, active, pres+fin, [], neg(_)), [varg(dir, np(3+sg, np_head(det(any), [], country), []))], []))]))], []))), sem((answer80([]):-A^ (ocean(A), \+B^ (country(B), borders(A, B))))), qplan((answer80([]):-A^{ocean(A), {\+B^ (borders(A, B), {country(B)})}})), 
 1076answers([true])],[time(0.0010000000000000009)]).
 1077must_test_801([what, are, the, countries, from, which, a, river, flows, into, the, black_sea, ?], [sent([what, are, the, countries, from, which, a, river, flows, into, the, black_sea, ?]), parse(whq(feature&place&country-B, s(np(3+pl, wh(feature&place&country-B), []), verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+pl, np_head(det(the(pl)), [], country), [rel(feature&place&country-D, s(np(3+sg, np_head(det(a), [], river), []), verb(flow, active, pres+fin, [], pos(_)), [], [pp(prep(from), np(3+pl, wh(feature&place&country-D), [])), pp(prep(into), np(3+sg, name(black_sea), []))]))]))], []))), sem((answer80([A]):-setof(B, (country(B), C^ (river(C), flows(C, B, black_sea))), A))), qplan((answer80([C]):-setof(B, A^ (flows(A, B, black_sea), {country(B)}, {river(A)}), C))), 
 1078answers([[romania]])],[time(0.0010000000000000009)]).
 1079must_test_801([which, countries, have, a, population, exceeding, nquant(10), million, ?], [sent([which, countries, have, a, population, exceeding, nquant(10), million, ?]), parse(whq(feature&place&country-B, s(np(3+pl, np_head(int_det(feature&place&country-B), [], country), []), verb(have, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(det(a), [], population), [reduced_rel(measure&countables-C, s(np(3+sg, wh(measure&countables-C), []), verb(exceed, active, inf, [prog], pos(_)), [varg(dir, np(3+pl, np_head(quant(same, nquant(10)), [], million), []))], []))]))], []))), sem((answer80([A]):-country(A), B^ (exceeds(B, 10--million), population(A, B)))), qplan((answer80([A]):-B^ (country(A), {population(A, B), {exceeds(B, 10--million)}}))), 
 1080answers([malaysia, uganda])],[time(0.0010000000000000009)]).
 1081must_test_801([which, countries, with, a, population, exceeding, nquant(10), million, border, the, atlantic, ?], [sent([which, countries, with, a, population, exceeding, nquant(10), million, border, the, atlantic, ?]), parse(whq(feature&place&country-B, s(np(3+pl, np_head(int_det(feature&place&country-B), [], country), [pp(prep(with), np(3+sg, np_head(det(a), [], population), [reduced_rel(measure&countables-C, s(np(3+sg, wh(measure&countables-C), []), verb(exceed, active, inf, [prog], pos(_)), [varg(dir, np(3+pl, np_head(quant(same, nquant(10)), [], million), []))], []))]))]), verb(border, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, name(atlantic), []))], []))), sem((answer80([A]):-B^ (population(A, B), exceeds(B, 10--million), country(A)), borders(A, atlantic))), qplan((answer80([A]):-B^ (borders(A, atlantic), {population(A, B), {exceeds(B, 10--million)}}, {country(A)}))), 
 1082answers([venezuela])],[time(0.0010000000000000009)]).
 1083
 1084must_test_801([what, countries, are, there, in, europe, ?], [sent([what, countries, are, there, in, europe, ?]), parse(whq(feature&place&country-B, s(np(3+pl, np_head(int_det(feature&place&country-B), [], country), []), verb(be, active, pres+fin, [], pos(_)), [void], [pp(prep(in), np(3+sg, name(europe), []))]))), sem((answer80([A]):-country(A), in_ploc(A, europe))), qplan((answer80([A]):-in_ploc(A, europe), {country(A)})), 
 1085answers([albania, andorra, austria, belgium, bulgaria, cyprus, czechoslovakia, denmark, east_germany, eire, finland, france, greece, hungary, iceland, italy, liechtenstein, luxembourg, malta, monaco, netherlands, norway, poland, portugal, romania, san_marino, spain, sweden, switzerland, united_kingdom, west_germany, yugoslavia])],[time(0.0010000000000000009)]).
 1086
 1087must_test_801(U,R,O):-must_test_804(U,R,O).
 1088must_test_801(U,R,O):-must_test_802(U,R,O).
 1089must_test_801(U,R,O):-must_test_803(U,R,O).
 1090must_test_801(U,R,O):-must_test_806(U,R,O).
 1091must_test_801(U,R,O):-must_test_805(U,R,O).
 1092
 1093
 1094must_test_805([which, countries, with, a, population, exceeding, nquant(10), million, border, the, atlantic, ?], [sent([which, countries, with, a, population, exceeding, nquant(10), million, border, the, atlantic, ?]), parse(whq(feature&place&country-B, s(np(3+plu, np_head(int_det(feature&place&country-B), [], country), [pp(prep(with), np(3+sin, np_head(det(a), [], population), [reduced_rel(measure&heads-C, s(np(3+sin, wh(measure&heads-C), []), verb(exceed, active, inf, [prog], pos), [arg(dir, np(3+plu, np_head(quant(same, nquant(10)), [], million), []))], []))]))]), verb(border, active, pres+fin, [], pos), [arg(dir, np(3+sin, name(atlantic), []))], []))), sem((answer([A]):-B^ (population(A, B), exceeds(B, 10--million), country(A)), borders(A, atlantic))), qplan((answer([A]):-B^ (borders(A, atlantic), {population(A, B), {exceeds(B, 10--million)}}, {country(A)}))), answers([venezuela])],[time(0.0010000000000000009)]).
 1095must_test_806([which, countries, have, a, population, exceeding, nquant(10), million, ?], [sent([which, countries, have, a, population, exceeding, nquant(10), million, ?]), parse(whq(feature&place&country-B, s(np(3+plu, np_head(int_det(feature&place&country-B), [], country), []), verb(have, active, pres+fin, [], pos), [arg(dir, np(3+sin, np_head(det(a), [], population), [reduced_rel(measure&heads-C, s(np(3+sin, wh(measure&heads-C), []), verb(exceed, active, inf, [prog], pos), [arg(dir, np(3+plu, np_head(quant(same, nquant(10)), [], million), []))], []))]))], []))), sem((answer([A]):-country(A), B^ (exceeds(B, 10--million), population(A, B)))), qplan((answer([A]):-B^ (country(A), {population(A, B), {exceeds(B, 10--million)}}))), answers([malaysia, uganda])],[time(0.0010000000000000009)]).
 1096
 1097
 1098must_test_802([how, large, is, the, smallest, american, country, ?], [sent([how, large, is, the, smallest, american, country, ?]), parse(whq(measure&area-B, s(np(3+sg, np_head(det(the(sg)), [sup(most, adj(small)), adj(american)], country), []), verb(be, active, pres+fin, [], pos(_)), [varg(pred, value(adj(large), wh(measure&area-B)))], []))), sem((answer80([A]):-B^ (C^ (setof(D:E, (country(E), area(E, D), american(E)), C), aggregate80(min, C, B)), area(B, A)))), qplan((answer80([E]):-D^C^ (setof(B:A, (american(A), {country(A)}, area(A, B)), C), aggregate80(min, C, D), area(D, E)))), 
 1099answers([0--ksqmiles])],[time(0.0)]).
 1100must_test_802([what, is, the, total, area, of, countries, south, of, the, equator, and, not, in, australasia, ?], [sent([what, is, the, total, area, of, countries, south, of, the, equator, and, not, in, australasia, ?]), parse(whq(A-B, s(np(3+sg, wh(A-B), []), verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(det(the(sg)), [adj(total)], area), [pp(prep(of), np(3+pl, np_head(generic, [], country), [conj(and, reduced_rel(feature&place&country-F, s(np(3+pl, wh(feature&place&country-F), []), verb(be, active, pres+fin, [], pos(_)), [varg(pred, pp(prep(southof), np(3+sg, name(equator), [])))], [])), reduced_rel(feature&place&country-F, s(np(3+pl, wh(feature&place&country-F), []), verb(be, active, pres+fin, [], neg(_)), [varg(pred, pp(prep(in), np(3+sg, name(australasia), [])))], [])))]))]))], []))), sem((answer80([A]):-B^ (setof(C:[D], (area(D, C), country(D), southof(D, equator), \+in_ploc(D, australasia)), B), aggregate80(total, B, A)))), 
 1101qplan((answer80([E]):-D^ (setof(C:[B], (southof(B, equator), area(B, C), {country(B)}, {\+in_ploc(B, australasia)}), D), aggregate80(total, D, E)))), 
 1102answers([10239--ksqmiles])],[time(0.0010000000000000009)]).
 1103must_test_802([which, countries, are, bordered, by, two, seas, ?], [sent([which, countries, are, bordered, by, two, seas, ?]), parse(whq(feature&place&country-B, s(np(3+pl, np_head(int_det(feature&place&country-B), [], country), []), verb(border, passive, pres+fin, [], pos(_)), [], [pp(prep(by), np(3+pl, np_head(quant(same, nquant(2)), [], sea), []))]))), 
 1104sem((answer80([A]):-country(A), numberof(B, (sea(B), borders(B, A)), 2))), 
 1105qplan((answer80([B]):-numberof(A, (sea(A), borders(A, B)), 2), {country(B)})), 
 1106answers([egypt, iran, israel, saudi_arabia, turkey])],[time(0.0)]).
 1107
 1108must_test_803([which, country, bordering, the, mediterranean, borders, a, country, that, is, bordered, by, a, country, whose, population, exceeds, the, population, of, india, ?], [sent([which, country, bordering, the, mediterranean, borders, a, country, that, is, bordered, by, a, country, whose, population, exceeds, the, population, of, india, ?]), parse(whq(feature&place&country-B, s(np(3+sg, np_head(int_det(feature&place&country-B), [], country), [reduced_rel(feature&place&country-B, s(np(3+sg, wh(feature&place&country-B), []), verb(border, active, inf, [prog], pos(_)), [varg(dir, np(3+sg, name(mediterranean), []))], []))]), verb(border, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(det(a), [], country), [rel(feature&place&country-C, s(np(3+sg, wh(feature&place&country-C), []), verb(border, passive, pres+fin, [], pos(_)), [], [pp(prep(by), np(3+sg, np_head(det(a), [], country), [rel(feature&place&country-D, s(np(3+sg, np_head(det(the(sg)), [], population), [pp(poss, np(3+sg, wh(feature&place&country-D), []))]), verb(exceed, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(det(the(sg)), [], population), [pp(prep(of), np(3+sg, name(india), []))]))], []))]))]))]))], []))), 
 1109sem((answer80([A]):-country(A), borders(A, mediterranean), B^ (country(B), C^ (country(C), D^ (population(C, D), E^ (population(india, E), exceeds(D, E))), borders(C, B)), borders(A, B)))), qplan((answer80([B]):-C^D^E^A^ (population(india, A), borders(B, mediterranean), {country(B)}, {borders(B, C), {country(C)}, {borders(D, C), {country(D)}, {population(D, E), {exceeds(E, A)}}}}))), 
 1110answers([turkey])],[time(0.0020000000000000018)]).
 1111must_test_803([which, country, '\'', s, capital, is, london, ?], [sent([which, country, '\'', s, capital, is, london, ?]), parse(whq(feature&place&country-B, s(np(3+sg, np_head(det(the(sg)), [], capital), [pp(poss, np(3+sg, np_head(int_det(feature&place&country-B), [], country), []))]), verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, name(london), []))], []))), sem((answer80([A]):-country(A), capital(A, london))), 
 1112qplan((answer80([A]):-capital(A, london), {country(A)})), 
 1113answers([united_kingdom])],[time(0.0010000000000000009)]).
 1114must_test_803([what, are, the, continents, no, country, in, which, contains, more, than, two, cities, whose, population, exceeds, nquant(1), million, ?], [sent([what, are, the, continents, no, country, in, which, contains, more, than, two, cities, whose, population, exceeds, nquant(1), million, ?]), parse(whq(feature&place&continent-B, s(np(3+pl, wh(feature&place&continent-B), []), verb(be, active, pres+fin, [], pos(_)), [varg(dir, np(3+pl, np_head(det(the(pl)), [], continent), [rel(feature&place&continent-D, s(np(3+sg, np_head(det(no), [], country), [pp(prep(in), np(3+pl, wh(feature&place&continent-D), []))]), verb(contain, active, pres+fin, [], pos(_)), [varg(dir, np(3+pl, np_head(quant(more, nquant(2)), [], city), [rel(feature&city-G, s(np(3+sg, np_head(det(the(sg)), [], population), [pp(poss, np(3+pl, wh(feature&city-G), []))]), verb(exceed, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(quant(same, nquant(1)), [], million), []))], []))]))], []))]))], []))), 
 1115sem((answer80([F]):-setof(A, (continent(A), \+B^ (country(B), in_ploc(B, A), E^ (numberof(C, (city(C), D^ (population(C, D), exceeds(D, 1--million)), in_ploc(C, B)), E), E>2))), F))), qplan((answer80([L]):-setof(G, (continent(G), \+H^ (country(H), in_ploc(H, G), K^ (numberof(I, (city(I), J^ (population(I, J), exceeds(J, 1--million)), in_ploc(I, H)), K), K>2))), L))), 
 1116answers([[africa, america, antarctica, asia, australasia, europe]])],[time(0.05499999999999999)]).
 1117
 1118must_test_804([what, percentage, of, countries, border, each, ocean, ?], 
 1119  [ sent([what, percentage, of, countries, border, each, ocean, ?]), 
 1120    parse(whq(A-C, s(np(3+pl, np_head(int_det(A-C), [], percentage), [pp(prep(of), np(3+pl, np_head(generic, [], country), []))]), verb(border, active, pres+fin, [], pos(_)), [varg(dir, np(3+sg, np_head(det(each), [], ocean), []))], []))), sem((answer80([B, E]):-ocean(B), [afghanistan, albania, algeria, andorra, angola, argentina, australia, austria, bahamas, bahrain, bangladesh, barbados, belgium, belize, bhutan, bolivia, botswana, brazil, bulgaria, burma, burundi, cambodia, cameroon, canada, central_african_republic, chad, chile, china, colombia, congo, costa_rica, cuba, cyprus, czechoslovakia, dahomey, denmark, djibouti, dominican_republic, east_germany, ecuador, egypt, eire, el_salvador, equatorial_guinea, ethiopia, fiji, finland, france, french_guiana, gabon, gambia, ghana, greece, grenada, guatemala, guinea, guinea_bissau, guyana, haiti, honduras, hungary, iceland, india, indonesia, iran, iraq, israel, italy, ivory_coast, jamaica, japan, jordan, kenya, kuwait, laos, lebanon, lesotho, liberia, libya, liechtenstein, luxembourg, malagasy, malawi, malaysia, maldives, mali, malta, mauritania, mauritius, mexico, monaco, mongolia, morocco, mozambique, nepal, netherlands, new_zealand, nicaragua, niger, nigeria, north_korea, norway, oman, pakistan, panama, papua_new_guinea, paraguay, peru, philippines, poland, portugal, qatar, romania, rwanda, san_marino, saudi_arabia, senegal, seychelles, sierra_leone, singapore, somalia, south_africa, south_korea, south_yemen, soviet_union, spain, sri_lanka, sudan, surinam, swaziland, sweden, switzerland, syria, taiwan, tanzania, thailand, togo, tonga, trinidad_and_tobago, tunisia, turkey, uganda, united_arab_emirates, united_kingdom, united_states, upper_volta, uruguay, venezuela, vietnam, west_germany, western_samoa, yemen, yugoslavia, zaire, zambia, zimbabwe]^ (setof(C, country(C), [afghanistan, albania, algeria, andorra, angola, argentina, australia, austria, bahamas, bahrain, bangladesh, barbados, belgium, belize, bhutan, bolivia, botswana, brazil, bulgaria, burma, burundi, cambodia, cameroon, canada, central_african_republic, chad, chile, china, colombia, congo, costa_rica, cuba, cyprus, czechoslovakia, dahomey, denmark, djibouti, dominican_republic, east_germany, ecuador, egypt, eire, el_salvador, equatorial_guinea, ethiopia, fiji, finland, france, french_guiana, gabon, gambia, ghana, greece, grenada, guatemala, guinea, guinea_bissau, guyana, haiti, honduras, hungary, iceland, india, indonesia, iran, iraq, israel, italy, ivory_coast, jamaica, japan, jordan, kenya, kuwait, laos, lebanon, lesotho, liberia, libya, liechtenstein, luxembourg, malagasy, malawi, malaysia, maldives, mali, malta, mauritania, mauritius, mexico, monaco, mongolia, morocco, mozambique, nepal, netherlands, new_zealand, nicaragua, niger, nigeria, north_korea, norway, oman, pakistan, panama, papua_new_guinea, paraguay, peru, philippines, poland, portugal, qatar, romania, rwanda, san_marino, saudi_arabia, senegal, seychelles, sierra_leone, singapore, somalia, south_africa, south_korea, south_yemen, soviet_union, spain, sri_lanka, sudan, surinam, swaziland, sweden, switzerland, syria, taiwan, tanzania, thailand, togo, tonga, trinidad_and_tobago, tunisia, turkey, uganda, united_arab_emirates, united_kingdom, united_states, upper_volta, uruguay, venezuela, vietnam, west_germany, western_samoa, yemen, yugoslavia, zaire, zambia, zimbabwe]), 4^ (numberof(D, (one_of([afghanistan, albania, algeria, andorra, angola, argentina, australia, austria, bahamas, bahrain, bangladesh, barbados, belgium, belize, bhutan, bolivia, botswana, brazil, bulgaria, burma, burundi, cambodia, cameroon, canada, central_african_republic, chad, chile, china, colombia, congo, costa_rica, cuba, cyprus, czechoslovakia, dahomey, denmark, djibouti, dominican_republic, east_germany, ecuador, egypt, eire, el_salvador, equatorial_guinea, ethiopia, fiji, finland, france, french_guiana, gabon, gambia, ghana, greece, grenada, guatemala, guinea, guinea_bissau, guyana, haiti, honduras, hungary, iceland, india, indonesia, iran, iraq, israel, italy, ivory_coast, jamaica, japan, jordan, kenya, kuwait, laos, lebanon, lesotho, liberia, libya, liechtenstein, luxembourg, malagasy, malawi, malaysia, maldives, mali, malta, mauritania, mauritius, mexico, monaco, mongolia, morocco, mozambique, nepal, netherlands, new_zealand, nicaragua, niger, nigeria, north_korea, norway, oman, pakistan, panama, papua_new_guinea, paraguay, peru, philippines, poland, portugal, qatar, romania, rwanda, san_marino, saudi_arabia, senegal, seychelles, sierra_leone, singapore, somalia, south_africa, south_korea, south_yemen, soviet_union, spain, sri_lanka, sudan, surinam, swaziland, sweden, switzerland, syria, taiwan, tanzania, thailand, togo, tonga, trinidad_and_tobago, tunisia, turkey, uganda, united_arab_emirates, united_kingdom, united_states, upper_volta, uruguay, venezuela, vietnam, west_germany, western_samoa, yemen, yugoslavia, zaire, zambia, zimbabwe], D), borders(D, B)), 4), 156^ (card([afghanistan, albania, algeria, andorra, angola, argentina, australia, austria, bahamas, bahrain, bangladesh, barbados, belgium, belize, bhutan, bolivia, botswana, brazil, bulgaria, burma, burundi, cambodia, cameroon, canada, central_african_republic, chad, chile, china, colombia, congo, costa_rica, cuba, cyprus, czechoslovakia, dahomey, denmark, djibouti, dominican_republic, east_germany, ecuador, egypt, eire, el_salvador, equatorial_guinea, ethiopia, fiji, finland, france, french_guiana, gabon, gambia, ghana, greece, grenada, guatemala, guinea, guinea_bissau, guyana, haiti, honduras, hungary, iceland, india, indonesia, iran, iraq, israel, italy, ivory_coast, jamaica, japan, jordan, kenya, kuwait, laos, lebanon, lesotho, liberia, libya, liechtenstein, luxembourg, malagasy, malawi, malaysia, maldives, mali, malta, mauritania, mauritius, mexico, monaco, mongolia, morocco, mozambique, nepal, netherlands, new_zealand, nicaragua, niger, nigeria, north_korea, norway, oman, pakistan, panama, papua_new_guinea, paraguay, peru, philippines, poland, portugal, qatar, romania, rwanda, san_marino, saudi_arabia, senegal, seychelles, sierra_leone, singapore, somalia, south_africa, south_korea, south_yemen, soviet_union, spain, sri_lanka, sudan, surinam, swaziland, sweden, switzerland, syria, taiwan, tanzania, thailand, togo, tonga, trinidad_and_tobago, tunisia, turkey, uganda, united_arab_emirates, united_kingdom, united_states, upper_volta, uruguay, venezuela, vietnam, west_germany, western_samoa, yemen, yugoslavia, zaire, zambia, zimbabwe], 156), ratio(4, 156, E)))))), qplan((answer80([F, L]):-ocean(F), H^ (setof(G, country(G), H), J^ (numberof(I, (one_of(H, I), borders(I, F)), J), K^ (card(H, K), ratio(J, K, L)))))), 
 1121    answers([
 1122         [arctic_ocean,2.5641025641025643], 
 1123         [atlantic,35.2564], 
 1124         [indian_ocean,14.1026], 
 1125         [pacific,20.5128]])],
 1126  [time(0.0020000000000000018)]).
 1127% answers([[arctic_ocean, 2.5641025641025643]])],[time(0.0020000000000000018)]).
 1128
 1129:- share_mp((t11/0,t12/0,t13/0,t14/0,t15/0,t16/0)). 1130t11:- locally_hide(lmconf:use_cyc_database,locally(t_l:tracing80, forall(must_test_801(U,R,O),once(ignore(must(process_run_diff(report,U,R,O))))))).
 1131t12:- locally_hide(lmconf:use_cyc_database,locally(t_l:tracing80, forall(must_test_802(U,R,O),once(ignore(must(process_run_diff(report,U,R,O))))))).
 1132t13:- locally_hide(lmconf:use_cyc_database,locally(t_l:tracing80, forall(must_test_803(U,R,O),once(ignore(must(process_run_diff(report,U,R,O))))))).
 1133t14:- locally_hide(lmconf:use_cyc_database,locally(t_l:tracing80, forall(must_test_804(U,R,O),once(ignore(must(process_run_diff(report,U,R,O))))))).
 1134
 1135
 1136answer804([OCEAN, RATIO]):-
 1137 ocean(OCEAN),
 1138  satisfy((
 1139      ALL^(setof(C, country(C), ALL), 
 1140        COUNT_BORDER^(numberof(BC,  (one_of(ALL, BC), borders(BC, OCEAN)), COUNT_BORDER),
 1141            COUNT_ALL^(card(ALL, COUNT_ALL), 
 1142      ratio(COUNT_BORDER, COUNT_ALL, RATIO))))
 1143      )).
 1144t15:- forall(answer804([OCEAN, RATIO]),wdmsg(answer804([OCEAN, RATIO]))).
 1145
 1146t16:- locally_hide(lmconf:use_cyc_database,locally(t_l:tracing80, forall(must_test_805(U,R,O),once(ignore(must(process_run_diff(report,U,R,O))))))).
 1147t17:- locally_hide(lmconf:use_cyc_database,locally(t_l:tracing80, forall(must_test_806(U,R,O),once(ignore(must(process_run_diff(report,U,R,O)))))))