1/*  Copyright 1986-2020 David H. D. Warren and Fernando C. N. Pereira
    2
    3    Permission is hereby granted, free of charge, to any person obtaining a
    4    copy of this software and associated documentation files (the
    5    "Software"), to deal in the Software without restriction, including
    6    without limitation the rights to use, copy, modify, merge, publish,
    7    distribute, sublicense, and/or sell copies of the Software, and to
    8    permit persons to whom the Software is furnished to do so, subject to
    9    the following conditions:
   10
   11    The above copyright notice and this permission notice shall be included
   12    in all copies or substantial portions of the Software.
   13
   14    THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS
   15    OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
   16    MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
   17    IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY
   18    CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT,
   19    TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
   20    SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
   21*/
   22
   23clausify(question(V0,P),(answer(V):-B)) :-
   24   quantify(P,Quants,[],R0),
   25   split_quants(question(V0),Quants,HQuants,[],BQuants,[]),
   26   chain_apply(BQuants,R0,R1),
   27   head_vars(HQuants,B,R1,V,V0).
   28
   29quantify(quant(Det,X,Head,Pred,Args,Y),Above,Right,true) :-
   30   close_tree(Pred,P2),
   31   quantify_args(Args,AQuants,P1),
   32   split_quants(Det,AQuants,Above,[Q|Right],Below,[]),
   33   pre_apply(Head,Det,X,P1,P2,Y,Below,Q).
   34quantify(conj(Conj,LPred,LArgs,RPred,RArgs),Up,Up,P) :-
   35   close_tree(LPred,LP0),
   36   quantify_args(LArgs,LQs,LP1),
   37   chain_apply(LQs,(LP0,LP1),LP),
   38   close_tree(RPred,RP0),
   39   quantify_args(RArgs,RQs,RP1),
   40   chain_apply(RQs,(RP0,RP1),RP),
   41   conj_apply(Conj,LP,RP,P).
   42quantify(pred(Subj,Op,Head,Args),Above,Right,P) :-
   43   quantify(Subj,SQuants,[],P0),
   44   quantify_args(Args,AQuants,P1),
   45   split_quants(Op,AQuants,Up,Right,Here,[]),
   46   conc(SQuants,Up,Above),
   47   chain_apply(Here,(P0,Head,P1),P2),
   48   op_apply(Op,P2,P).
   49quantify(~P,Q,Q,P).
   50quantify(P&Q,Above,Right,(S,T)) :-
   51   quantify(Q,Right0,Right,T),
   52   quantify(P,Above,Right0,S).
   53
   54head_vars([],P,P,L,L0) :-
   55   strip_types(L0,L).
   56head_vars([Quant|Quants],(P,R0),R,[X|V],V0) :-
   57   extract_var(Quant,P,X),
   58   head_vars(Quants,R0,R,V,V0).
   59
   60strip_types([],[]).
   61strip_types([_-X|L0],[X|L]) :-
   62   strip_types(L0,L).
   63
   64extract_var(quant(_,_-X,P,_-X),P,X).
   65
   66chain_apply(Q0,P0,P) :-
   67   sort_quants(Q0,Q,[]),
   68   chain_apply0(Q,P0,P).
   69
   70chain_apply0([],P,P).
   71chain_apply0([Q|Quants],P0,P) :-
   72   chain_apply0(Quants,P0,P1),
   73   det_apply(Q,P1,P).
   74
   75quantify_args([],[],true).
   76quantify_args([Arg|Args],Quants,(P,Q)) :-
   77   quantify_args(Args,Quants0,Q),
   78   quantify(Arg,Quants,Quants0,P).
   79
   80pre_apply(~Head,set(I),X,P1,P2,Y,Quants,Quant) :-
   81   indices(Quants,I,Indices,RestQ),
   82   chain_apply(RestQ,(Head,P1),P),
   83   setify(Indices,X,(P,P2),Y,Quant).
   84pre_apply(~Head,Det,X,P1,P2,Y,Quants,quant(Det,X,(P,P2),Y)) :-
   85 ( unit_det(Det);
   86   index_det(Det,_)),
   87   chain_apply(Quants,(Head,P1),P).
   88pre_apply(apply(F,P0),Det,X,P1,P2,Y,
   89      Quants0,quant(Det,X,(P3,P2),Y)) :-
   90   but_last(Quants0,quant(lambda,Z,P0,Z),Quants),
   91   chain_apply(Quants,(F,P1),P3).
   92pre_apply(aggr(F,Value,L,Head,Pred),Det,X,P1,P2,Y,Quants,
   93      quant(Det,X,
   94            (S^(setof(Range:Domain,P,S),
   95                aggregate(F,S,Value)),P2),Y)) :-
   96   close_tree(Pred,R),
   97   complete_aggr(L,Head,(R,P1),Quants,P,Range,Domain).
   98
   99but_last([X|L0],Y,L) :-
  100   but_last0(L0,X,Y,L).
  101
  102but_last0([],X,X,[]).
  103but_last0([X|L0],Y,Z,[Y|L]) :-
  104   but_last0(L0,X,Z,L).
  105
  106close_tree(T,P) :-
  107   quantify(T,Q,[],P0),
  108   chain_apply(Q,P0,P).
  109
  110meta_apply(~G,R,Q,G,R,Q).
  111meta_apply(apply(F,(R,P)),R,Q0,F,true,Q) :-
  112   but_last(Q0,quant(lambda,Z,P,Z),Q).
  113
  114indices([],_,[],[]).
  115indices([Q|Quants],I,[Q|Indices],Rest) :-
  116   open_quant(Q,Det,_,_,_),
  117   index_det(Det,I),
  118   indices(Quants,I,Indices,Rest).
  119indices([Q|Quants],I,Indices,[Q|Rest]) :-
  120   open_quant(Q,Det,_,_,_),
  121   unit_det(Det),
  122   indices(Quants,I,Indices,Rest).
  123
  124setify([],Type-X,P,Y,quant(set,Type-([]:X),true:P,Y)).
  125setify([Index|Indices],X,P,Y,Quant) :-
  126   pipe(Index,Indices,X,P,Y,Quant).
  127
  128pipe(quant(int_det(_,Z),Z,P1,Z),
  129      Indices,X,P0,Y,quant(det(a),X,P,Y)) :-
  130   chain_apply(Indices,(P0,P1),P).
  131pipe(quant(index(_),_-Z,P0,_-Z),Indices,Type-X,P,Y,
  132      quant(set,Type-([Z|IndexV]:X),(P0,P1):P,Y)) :-
  133   index_vars(Indices,IndexV,P1).
  134
  135index_vars([],[],true).
  136index_vars([quant(index(_),_-X,P0,_-X)|Indices],
  137      [X|IndexV],(P0,P)) :-
  138   index_vars(Indices,IndexV,P).
  139
  140complete_aggr([Att,Obj],~G,R,Quants,(P,R),Att,Obj) :-
  141   chain_apply(Quants,G,P).
  142complete_aggr([Att],Head,R0,Quants0,(P1,P2,R),Att,Obj) :-
  143   meta_apply(Head,R0,Quants0,G,R,Quants),
  144   set_vars(Quants,Obj,Rest,P2),
  145   chain_apply(Rest,G,P1).
  146complete_aggr([],~G,R,[quant(set,_-(Obj:Att),S:T,_)],
  147      (G,R,S,T),Att,Obj).
  148
  149set_vars([quant(set,_-(I:X),P:Q,_-X)],[X|I],[],(P,Q)).
  150set_vars([],[],[],true).
  151set_vars([Q|Qs],[I|Is],R,(P,Ps)) :-
  152   open_quant(Q,Det,X,P,Y),
  153   set_var(Det,X,Y,I), !,
  154   set_vars(Qs,Is,R,Ps).
  155set_vars([Q|Qs],I,[Q|R],P) :-
  156   set_vars(Qs,I,R,P).
  157
  158set_var(Det,_-X,_-X,X) :-
  159   setifiable(Det).
  160
  161sort_quants([],L,L).
  162sort_quants([Q|Qs],S,S0) :-
  163   open_quant(Q,Det,_,_,_),
  164   split_quants(Det,Qs,A,[],B,[]),
  165   sort_quants(A,S,[Q|S1]),
  166   sort_quants(B,S1,S0).
  167
  168split_quants(_,[],A,A,B,B).
  169split_quants(Det0,[Quant|Quants],Above,Above0,Below,Below0) :-
  170   compare_dets(Det0,Quant,Above,Above1,Below,Below1),
  171   split_quants(Det0,Quants,Above1,Above0,Below1,Below0).
  172
  173compare_dets(Det0,Q,[quant(Det,X,P,Y)|Above],Above,Below,Below) :-
  174   open_quant(Q,Det1,X,P,Y),
  175   governs(Det1,Det0), !,
  176   bubble(Det0,Det1,Det).
  177compare_dets(Det0,Q0,Above,Above,[Q|Below],Below) :-
  178   lower(Det0,Q0,Q).
  179
  180open_quant(quant(Det,X,P,Y),Det,X,P,Y).
  181
  182% =================================================================
  183% Determiner Properties
  184
  185index_det(index(I),I).
  186index_det(int_det(I,_),I).
  187
  188unit_det(set).
  189unit_det(lambda).
  190unit_det(quant(_,_)).
  191unit_det(det(_)).
  192unit_det(question(_)).
  193unit_det(id).
  194unit_det(void).
  195unit_det(not).
  196unit_det(generic).
  197unit_det(int_det(_)).
  198unit_det(proportion(_)).
  199
  200det_apply(quant(Det,Type-X,P,_-Y),Q0,Q) :-
  201   apply(Det,Type,X,P,Y,Q0,Q).
  202
  203apply(generic,_,X,P,X,Q,X^(P,Q)).
  204apply(proportion(Type-V),_,X,P,Y,Q,
  205      S^(setof(X,P,S),
  206         N^(numberof(Y,(one_of(S,Y),Q),N),
  207            M^(card(S,M),ratio(N,M,V))))).
  208apply(id,_,X,P,X,Q,(P,Q)).
  209apply(void,_,X,P,X,Q,X^(P,Q)).
  210apply(set,_,Index:X,P0,S,Q,S^(P,Q)) :-
  211   apply_set(Index,X,P0,S,P).
  212apply(int_det(Type-X),Type,X,P,X,Q,(P,Q)).
  213apply(index(_),_,X,P,X,Q,X^(P,Q)).
  214apply(quant(Op,N),Type,X,P,X,Q,R) :-
  215   value(N,Type,Y),
  216   quant_op(Op,Z,Y,numberof(X,(P,Q),Z),R).
  217apply(det(Det),_,X,P,Y,Q,R) :-
  218   apply0(Det,X,P,Y,Q,R).
  219
  220apply0(Some,X,P,X,Q,X^(P,Q)) :-
  221   some(Some).
  222apply0(All,X,P,X,Q,\+X^(P,\+Q)) :-
  223   all(All).
  224apply0(no,X,P,X,Q,\+X^(P,Q)).
  225apply0(notall,X,P,X,Q,X^(P,\+Q)).
  226
  227quant_op(same,X,X,P,P).
  228quant_op(Op,X,Y,P,X^(P,F)) :-
  229   quant_op(Op,X,Y,F).
  230
  231quant_op(not+more,X,Y,X=<Y).
  232quant_op(not+less,X,Y,X>=Y).
  233quant_op(less,X,Y,X<Y).
  234quant_op(more,X,Y,X>Y).
  235
  236value(wh(Type-X),Type,X).
  237value(nb(X),_,X).
  238
  239all(all).
  240all(every).
  241all(each).
  242all(any).
  243
  244some(a).
  245some(the(sin)).
  246some(some).
  247
  248apply_set([],X,true:P,S,setof(X,P,S)).
  249apply_set([I|Is],X,Range:P,S,
  250      setof([I|Is]:V,(Range,setof(X,P,V)),S)).
  251
  252
  253governs(Det,set(J)) :-
  254   index_det(Det,I),
  255   I \== J.
  256governs(Det0,Det) :-
  257   index_det(Det0,_),
  258 ( index_det(Det,_);
  259   Det=det(_);
  260   Det=quant(_,_)).
  261governs(_,void).
  262governs(_,lambda).
  263governs(_,id).
  264governs(det(each),question([_|_])).
  265governs(det(each),det(each)).
  266governs(det(any),not).
  267governs(quant(same,wh(_)),Det) :-
  268   weak(Det).
  269
  270governs(det(Strong),Det) :-
  271   strong0(Strong),
  272   weak(Det).
  273
  274strong(det(Det)) :-
  275   strong0(Det).
  276
  277strong0(each).
  278strong0(any).
  279
  280weak(det(Det)) :-
  281   weak0(Det).
  282weak(quant(_,_)).
  283weak(index(_)).
  284weak(int_det(_,_)).
  285weak(set(_)).
  286weak(int_det(_)).
  287weak(generic).
  288weak(proportion(_)).
  289
  290weak0(no).
  291weak0(a).
  292weak0(all).
  293weak0(some).
  294weak0(every).
  295weak0(the(sin)).
  296weak0(notall).
  297
  298lower(question(_),Q,quant(det(a),X,P,Y)) :-
  299   open_quant(Q,det(any),X,P,Y), !.
  300lower(_,Q,Q).
  301
  302setifiable(generic).
  303setifiable(det(a)).
  304setifiable(det(all)).
  305
  306% =================================================================
  307% Operators (currently, identity, negation and 'and')
  308
  309op_apply(id,P,P).
  310op_apply(not,P,\+P).
  311
  312bubble(not,det(any),det(every)) :- !.
  313bubble(_,D,D).
  314
  315
  316conj_apply(and,P,Q,(P,Q))