1/*
    2 _________________________________________________________________________
    3|	Copyright (C) 1982						  |
    4|									  |
    5|	David Warren,							  |
    6|		SRI International, 333 Ravenswood Ave., Menlo Park,	  |
    7|		California 94025, USA;					  |
    8|									  |
    9|	Fernando Pereira,						  |
   10|		Dept. of Architecture, University of Edinburgh,		  |
   11|		20 Chambers St., Edinburgh EH1 1JZ, Scotland		  |
   12|									  |
   13|	This program may be used, copied, altered or included in other	  |
   14|	programs only for academic purposes and provided that the	  |
   15|	authorship of the initial program is aknowledged.		  |
   16|	Use for commercial purposes without the previous written 	  |
   17|	agreement of the authors is forbidden.				  |
   18|_________________________________________________________________________|
   19
   20*/
   21
   22clausify80(question80(V0,P),(answer80(V):-B)) :- !,
   23   quantify(P,Quants,[],R0),
   24   split_quants(question80(V0),Quants,HQuants,[],BQuants,[]),
   25   chain_apply(BQuants,R0,R1),
   26   head_vars(HQuants,B,R1,V,V0).
   27
   28clausify80(assertion(V0,P),(assertion80(V):-B)) :- nonvar(P),
   29   quantify(P,Quants,[],R0),
   30   split_quants(question80(V0),Quants,HQuants,[],BQuants,[]),
   31   chain_apply(BQuants,R0,R1),
   32   head_vars(HQuants,B,R1,V,V0).
   33
   34
   35quantify(quant(Det,X,Head,Pred,Args,Y),Above,Right,true) :-
   36   close_tree(Pred,P2),
   37   quantify_args(Args,AQuants,P1),
   38   split_quants(Det,AQuants,Above,[Q|Right],Below,[]),
   39   pre_apply(Head,Det,X,P1,P2,Y,Below,Q).
   40quantify(conj(Conj,LPred,LArgs,RPred,RArgs),Up,Up,P) :-
   41   close_tree(LPred,LP0),
   42   quantify_args(LArgs,LQs,LP1),
   43   chain_apply(LQs,(LP0,LP1),LP),
   44   close_tree(RPred,RP0),
   45   quantify_args(RArgs,RQs,RP1),
   46   chain_apply(RQs,(RP0,RP1),RP),
   47   conj_apply(Conj,LP,RP,P).
   48quantify(pred(Subj,Op,Head,Args),Above,Right,P) :-
   49   quantify(Subj,SQuants,[],P0),
   50   quantify_args(Args,AQuants,P1),
   51   split_quants(Op,AQuants,Up,Right,Here,[]),
   52   conc80(SQuants,Up,Above),
   53   chain_apply(Here,(P0,Head,P1),P2),
   54   op_apply(Op,P2,P).
   55quantify(~(P),Q,Q,P).
   56quantify(P&Q,Above,Right,(S,T)) :-
   57   quantify(Q,Right0,Right,T),
   58   quantify(P,Above,Right0,S).
   59   
   60head_vars([],P,P,L,L0) :-
   61   strip_types(L0,L).
   62head_vars([Quant|Quants],(P,R0),R,[X|V],V0) :-
   63   extract_var(Quant,P,X),
   64   head_vars(Quants,R0,R,V,V0).
   65
   66strip_types([],[]).
   67strip_types([_-X|L0],[X|L]) :-
   68   strip_types(L0,L).
   69
   70conc80([],L,L).
   71conc80([H|T],L,[H|R]) :- conc80(T,L,R).
   72
   73
   74extract_var(quant(_,_-X,P,_-X),P,X).
   75
   76chain_apply(Q0,P0,P) :-
   77   sort_quants(Q0,Q,[]),
   78   chain_apply0(Q,P0,P).    
   79
   80chain_apply0([],P,P).
   81chain_apply0([Q|Quants],P0,P) :-
   82   chain_apply0(Quants,P0,P1),
   83   det_apply(Q,P1,P).
   84
   85quantify_args([],[],true).
   86quantify_args([Arg|Args],Quants,(P,Q)) :-
   87   quantify_args(Args,Quants0,Q),
   88   quantify(Arg,Quants,Quants0,P).
   89
   90pre_apply(~Head,set(I),X,P1,P2,Y,Quants,Quant) :-
   91   indices(Quants,I,Indices,RestQ),
   92   chain_apply(RestQ,(Head,P1),P),
   93   setify(Indices,X,(P,P2),Y,Quant).
   94pre_apply(~Head,Det,X,P1,P2,Y,Quants,quant(Det,X,(P,P2),Y)) :-
   95 ( unit_det(Det);
   96   index_det(Det,_)),
   97   chain_apply(Quants,(Head,P1),P).
   98pre_apply(apply(F,P0),Det,X,P1,P2,Y,
   99      Quants0,quant(Det,X,(P3,P2),Y)) :-
  100   but_last(Quants0,quant(lambda,Z,P0,Z),Quants),
  101   chain_apply(Quants,(F,P1),P3).
  102pre_apply(aggr(F,Value,L,Head,Pred),Det,X,P1,P2,Y,Quants,
  103      quant(Det,X,
  104            (S^(setof(Range:Domain,P,S),
  105                aggregate80(F,S,Value)),P2),Y)) :-
  106   close_tree(Pred,R),
  107   complete_aggr(L,Head,(R,P1),Quants,P,Range,Domain).
  108
  109but_last([X|L0],Y,L) :-
  110   but_last0(L0,X,Y,L).
  111
  112but_last0([],X,X,[]).
  113but_last0([X|L0],Y,Z,[Y|L]) :-
  114   but_last0(L0,X,Z,L).
  115
  116close_tree(T,P) :-
  117   quantify(T,Q,[],P0),
  118   chain_apply(Q,P0,P).
  119
  120meta_apply(~(G),R,Q,G,R,Q).
  121meta_apply(apply(F,(R,P)),R,Q0,F,true,Q) :-
  122   but_last(Q0,quant(lambda,Z,P,Z),Q).
  123
  124indices([],_,[],[]).
  125indices([Q|Quants],I,[Q|Indices],Rest) :-
  126   open_quant(Q,Det,_,_,_),
  127   index_det(Det,I),
  128   indices(Quants,I,Indices,Rest).
  129indices([Q|Quants],I,Indices,[Q|Rest]) :-
  130   open_quant(Q,Det,_,_,_),
  131   unit_det(Det),
  132   indices(Quants,I,Indices,Rest).
  133
  134setify([],Type-X,P,Y,quant(set,Type-([]:X),true:P,Y)).
  135setify([Index|Indices],X,P,Y,Quant) :-
  136   pipe(Index,Indices,X,P,Y,Quant).
  137
  138pipe(quant(int_det(_,Z),Z,P1,Z),
  139      Indices,X,P0,Y,quant(det(a),X,P,Y)) :-
  140   chain_apply(Indices,(P0,P1),P).
  141pipe(quant(index(_),_-Z,P0,_-Z),Indices,Type-X,P,Y,
  142      quant(set,Type-([Z|IndexV]:X),(P0,P1):P,Y)) :-
  143   index_vars(Indices,IndexV,P1).
  144
  145index_vars([],[],true).
  146index_vars([quant(index(_),_-X,P0,_-X)|Indices],
  147      [X|IndexV],(P0,P)) :-
  148   index_vars(Indices,IndexV,P).
  149
  150complete_aggr([Att,Obj],~(G),R,Quants,(P,R),Att,Obj) :-
  151   chain_apply(Quants,G,P).
  152complete_aggr([Att],Head,R0,Quants0,(P1,P2,R),Att,Obj) :-
  153   meta_apply(Head,R0,Quants0,G,R,Quants),
  154   set_vars(Quants,Obj,Rest,P2),
  155   chain_apply(Rest,G,P1).
  156complete_aggr([],~(G),R,[quant(set,_-(Obj:Att),S:T,_)],
  157      (G,R,S,T),Att,Obj).
  158
  159set_vars([quant(set,_-(I:X),P:Q,_-X)],[X|I],[],(P,Q)).
  160set_vars([],[],[],true).
  161set_vars([Q|Qs],[I|Is],R,(P,Ps)) :-
  162   open_quant(Q,Det,X,P,Y),
  163   set_var(Det,X,Y,I), !,
  164   set_vars(Qs,Is,R,Ps).
  165set_vars([Q|Qs],I,[Q|R],P) :-
  166   set_vars(Qs,I,R,P).
  167
  168set_var(Det,_-X,_-X,X) :-
  169   setifiable(Det).
  170
  171sort_quants([],L,L).
  172sort_quants([Q|Qs],S,S0) :-
  173   open_quant(Q,Det,_,_,_),
  174   split_quants(Det,Qs,A,[],B,[]),
  175   sort_quants(A,S,[Q|S1]),
  176   sort_quants(B,S1,S0).
  177
  178split_quants(_,[],A,A,B,B).
  179split_quants(Det0,[Quant|Quants],Above,Above0,Below,Below0) :-
  180   compare_dets(Det0,Quant,Above,Above1,Below,Below1),
  181   split_quants(Det0,Quants,Above1,Above0,Below1,Below0).
  182
  183compare_dets(Det0,Q,[quant(Det,X,P,Y)|Above],Above,Below,Below) :-
  184   open_quant(Q,Det1,X,P,Y),
  185   governs_det(Det1,Det0), !,
  186   bubble(Det0,Det1,Det).
  187compare_dets(Det0,Q0,Above,Above,[Q|Below],Below) :-
  188   lower(Det0,Q0,Q).
  189
  190open_quant(quant(Det,X,P,Y),Det,X,P,Y).
  191
  192% =================================================================
  193% Determiner Properties
  194
  195index_det(index(I),I).
  196index_det(int_det(I,_),I).
  197
  198unit_det(set).
  199unit_det(lambda).
  200unit_det(quant(_,_)).
  201unit_det(det(_)).
  202unit_det(question80(_)).
  203unit_det(id(_Why)).
  204unit_det(void(_Meaning)).
  205unit_det(not(_Why)).
  206unit_det(generic).
  207unit_det(int_det(_)).
  208unit_det(proportion(_)).
  209
  210det_apply(quant(Det,Type-X,P,_-Y),Q0,Q) :-
  211   apply(Det,Type,X,P,Y,Q0,Q).
  212
  213apply(generic,_,X,P,X,Q,X^(P,Q)).
  214apply(proportion(_Type-V),_,X,P,Y,Q,
  215      S^(setof(X,P,S),
  216         N^(numberof(Y,(one_of(S,Y),Q),N),
  217            M^(card(S,M),ratio(N,M,V))))).
  218apply(id(_Why),_,X,P,X,Q,(P,Q)).
  219apply(void(_Meaning),_,X,P,X,Q,X^(P,Q)).
  220apply(set,_,Index:X,P0,S,Q,S^(P,Q)) :-
  221   apply_set(Index,X,P0,S,P).
  222apply(int_det(Type-X),Type,X,P,X,Q,(P,Q)).
  223apply(index(_),_,X,P,X,Q,X^(P,Q)).
  224apply(quant(Op,N),Type,X,P,X,Q,R) :-
  225   value(N,Type,Y),
  226   quant_op(Op,Z,Y,numberof(X,(P,Q),Z),R).
  227apply(det(Det),_,X,P,Y,Q,R) :-
  228   apply0(Det,X,P,Y,Q,R).
  229
  230apply0(Some,X,P,X,Q,X^(P,Q)) :-
  231   some(Some).
  232apply0(All,X,P,X,Q,\+X^(P,\+Q)) :-
  233   all(All).
  234apply0(no,X,P,X,Q,\+X^(P,Q)).
  235apply0(notall,X,P,X,Q,X^(P,\+Q)).
  236
  237quant_op(same,X,X,P,P).
  238quant_op(Op,X,Y,P,X^(P,F)) :-
  239   quant_op(Op,X,Y,F).
  240
  241quant_op(not(_Why)+more,X,Y,X=<Y).
  242quant_op(not(_Why)+less,X,Y,X>=Y).
  243quant_op(less,X,Y,X<Y).
  244quant_op(more,X,Y,X>Y).
  245
  246value(wh(Type-X),Type,X).
  247value(nquant(X),_,X).
  248
  249all(all).
  250all(every).
  251all(each).
  252all(any).
  253
  254some(a).
  255some(the(sg)).
  256some(some).
  257
  258apply_set([],X,true:P,S,setof(X,P,S)).
  259apply_set([I|Is],X,Range:P,S,
  260      setof([I|Is]:V,(Range,setof(X,P,V)),S)).
  261
  262governs_det(Det,_Det0):-must(nonvar(Det)),fail.
  263governs_det(Det,set(J)) :-
  264   index_det(Det,I),
  265   I \== J.
  266governs_det(Det0,Det) :-
  267   index_det(Det0,_),
  268 ( index_det(Det,_);
  269   Det=det(_);
  270   Det=quant(_,_)).
  271governs_det(_,void(_There)).
  272governs_det(_,lambda).
  273governs_det(_,id(_Why)).
  274governs_det(det(each),question80([_|_])).
  275governs_det(det(each),det(each)).
  276governs_det(det(any),not(_Why)).
  277governs_det(quant(same,wh(_)),Det) :-
  278   weak(Det).
  279governs_det(det(Strong),Det) :-
  280   strong0(Strong),
  281   weak(Det).
  282
  283strong(det(Det)) :-
  284   strong0(Det).
  285
  286strong0(each).
  287strong0(any).
  288
  289weak(det(Det)) :-
  290   weak0(Det).
  291weak(quant(_,_)).
  292weak(index(_)).
  293weak(int_det(_,_)).
  294weak(set(_)).
  295weak(int_det(_)).
  296weak(generic).
  297weak(proportion(_)).
  298
  299weak0(no).
  300weak0(a).
  301weak0(all).
  302weak0(some).
  303weak0(every).
  304weak0(the(sg)).
  305weak0(notall).
  306
  307lower(question80(_),Q,quant(det(a),X,P,Y)) :-
  308   open_quant(Q,det(any),X,P,Y), !.
  309lower(_,Q,Q).
  310
  311setifiable(generic).
  312setifiable(det(a)).
  313setifiable(det(all)).
  314
  315% =================================================================
  316% Operators (currently, identity, negation and 'and')
  317
  318op_apply(id(_Why),P,P).
  319op_apply(not(_Why),P,\+P).
  320
  321bubble(not(_Why),det(any),det(every)) :- !.
  322bubble(_,D,D).
  323
  324
  325conj_apply(and,P,Q,(P,Q))