2%% fluent.pl - CHR for SICSTUS
    3
    4%% $Id: fluent.chr, v 2.0 2004/01/22 00:26:00 $
    5%%
    6%% FLUX: a Prolog library for high-level programming of cognitive agents
    7%% Copyright 2003, 2004  Michael Thielscher
    8%% This file belongs to the flux kernel package distributed at
    9%%   http://www.fluxagent.org
   10%%
   11%% This library is free software; you can redistribute it and/or modify it
   12%% under the terms of the GNU Library General Public License as published by
   13%% the Free Software Foundation; either version 2 of the License, or (at your
   14%% option) any later version.
   15%%
   16%% This library is distributed in the hope that it will be useful, but WITHOUT
   17%% ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
   18%% FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Library General Public
   19%% License for more details.
   20%%
   21%% You should have received a copy of the GNU Library General Public License
   22%% along with this library; if not, write to the Free Software Foundation,
   23%% Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
   24%%
   25%% Consult the file COPYING for license details.
   26
   27
   28
   29%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   30%%
   31%% Preamble
   32%%
   33%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   34
   35handler fluent.
   36
   37constraints not_holds/2, not_holds_all/2, duplicate_free/1,
   38            or_holds/2, or_holds/3, cancel/2, cancelled/2.
   39
   40option(check_guard_bindings,off).
   41
   42
   43%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   44%%
   45%% Constraint Handling Rules for state constraints
   46%%
   47%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   48
   49
   50not_holds(F, [F1|Z]) <=> neq(F, F1), not_holds(F, Z).
   51not_holds(_, [])     <=> true.
   52
   53not_holds_all(F, [F1|Z]) <=> neq_all(F, F1), not_holds_all(F, Z).
   54not_holds_all(_, [])     <=> true.
   55
   56not_holds_all(F, Z) \ not_holds(G, Z)     <=> inst(G, F) | true.
   57not_holds_all(F, Z) \ not_holds_all(G, Z) <=> inst(G, F) | true.
   58
   59duplicate_free([F|Z]) <=> not_holds(F,Z), duplicate_free(Z).
   60duplicate_free([])    <=> true.
   61
   62or_holds([F],Z) <=> F\=eq(_,_) | fluent_holds_in_state(F,Z).
   63
   64or_holds(V,_Z) <=> \+ ( member(F,V),F\=eq(_,_) ) | or_and_eq(V,D), call(D).
   65
   66or_holds(V,[]) <=> member(F, V, W), F\=eq(_,_) | or_holds(W,[]).
   67
   68or_holds(V,_Z) <=> member(eq(X,Y),V), or_neq(exists,X,Y,D), \+ call(D) | true.
   69or_holds(V,Z) <=> member(eq(X,Y),V,W), \+ (and_eq(X,Y,D), call(D)) | or_holds(W,Z).
   70
   71not_holds(F, Z) \ or_holds(V, Z) <=> member(G, V, W), F==G | or_holds(W, Z).
   72
   73not_holds_all(F, Z) \ or_holds(V, Z) <=> member(G, V, W), inst(G, F)
   74                                         | or_holds(W, Z).
   75
   76or_holds(V, [F|Z]) <=> or_holds(V, [], [F|Z]).
   77
   78or_holds([G|V],W,[F|Z]) <=> true | ( G==F -> true ;
   79                            G\=F -> or_holds(V,[G|W],[F|Z]) ;
   80                            G=..[_|ArgX], F=..[_|ArgY],
   81                            or_holds(V,[eq(ArgX,ArgY),G|W],[F|Z])).
   82
   83or_holds([],W,[_|Z]) <=> or_holds(W,Z).
   84
   85
   86%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   87%%
   88%% Constraint Handling Rules for cancellation of constraints on a fluent
   89%%
   90%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   91
   92cancel(F,Z) \ not_holds(G,Z)     <=> \+ F\=G | true.
   93
   94cancel(F,Z) \ not_holds_all(G,Z) <=> \+ F\=G | true.
   95
   96cancel(F,Z) \ or_holds(V,Z)      <=> member(G,V), \+ F\=G | true.
   97
   98cancel(F,Z), cancelled(F,Z) <=> true.
   99
  100
  101%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  102%%
  103%% Auxiliary clauses
  104%%
  105%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  106
  107neq(F, F1)     :- or_neq(exists, F, F1).
  108neq_all(F, F1) :- or_neq(forall, F, F1).
  109
  110or_neq(Q, Fx, Fy) :-
  111  functor(Fx, F, M), functor(Fy, G, N),
  112  ( F=G, M=N -> Fx =.. [_|ArgX], Fy =.. [_|ArgY], or_neq(Q, ArgX, ArgY, D), call(D)
  113              ; true ).
  114
  115or_neq(_, [], [], (0#\=0)).
  116or_neq(Q, [X|X1], [Y|Y1], D) :-
  117  or_neq(Q, X1, Y1, D1),
  118  ( Q=forall, var(X), \+ is_domain(X) -> ( binding(X,X1,Y1,YE) ->
  119
  120                                         D=((Y#\=YE)#\/D1) ; D=D1 )
  121                                         ; D=((X#\=Y)#\/D1) ).
  122                                         
  123binding(X,[X1|ArgX],[Y1|ArgY],Y) :-
  124   X==X1 -> Y=Y1 ; binding(X,ArgX,ArgY,Y).
  125
  126and_eq([], [], (0#=0)).
  127and_eq([X|X1], [Y|Y1], D) :-
  128   and_eq(X1, Y1, D1),
  129   D = ((X#=Y)#/\D1).
  130
  131or_and_eq([], (0#\=0)).
  132or_and_eq([eq(X,Y)|Eq], (D1#\/D2)) :-   and_eq(X,Y,D1),   or_and_eq(Eq,D2).
  139inst(G,F) :- subsumes_chk(F,G), var_chk(G,F).
  140
  141var_chk(X,Y) :- var(Y), X==Y.
  142var_chk(_,Y) :- var(Y), \+ fd_var(Y).
  143var_chk(X,Y) :- is_list(Y), var_chk_list(X,Y).
  144var_chk(X,Y) :- compound(Y), \+ is_list(Y), X=..[_|Xs], Y=..[_|Ys], var_chk_list(Xs,Ys).
  145
  146var_chk_list([],[]).
  147var_chk_list([X|Xs],[Y|Ys]) :- var_chk(X,Y), var_chk_list(Xs,Ys).
  148
  149member(X, [X|T], T).
  150member(X, [H|T], [H|T1]) :- member(X, T, T1).
  151
  152is_domain(X) :- fd_var(X), \+ ( fd_max(X,sup), fd_min(X,inf))