1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2%
    3%       World Smallest Iterative Deeping Forward Filtering 
    4%		Conditional Planner		
    5%		(Version with constraints for ECLIPSE Prolog) 
    6%       Tested with ECLIPSE 5.3 and SWI Prolog over Linux RH 7.0-7.2
    7%
    8%	c) 	Hector J. Levesque      		Many rights reserved	(Nov 2001)
    9% 		Modified by Sebastian Sardina    Many rights reserved	(Jan 2002)
   10%
   11%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   12% This file provides the following:
   13% 
   14%  --- wscp(Name,Goal,Max,IA,SimNo,S,Plan):  Plan for Goal up to depth Max
   15%      wscp(Name,Goal,Max,S,Plan)
   16%            Name : symbolic name of the planning problem
   17%            Goal : goal 
   18%            Max  : max depth to search for 
   19%            IA   : initial set of actions to use
   20%            SimNo: Use SimNo simulator controller for exogenous actions
   21%            S    : initial history/situation
   22%            Plan : plan
   23%
   24%  --- pplan(Name,Goal,Max,End): 
   25%      pplan(Goal,Max) [Name=Goal and End=true]
   26%      pplan(Name,Goal,Max) [End=true]
   27%           plan for Goal up to Max depth. At the end print
   28%              the plan using End as the final condition to print out
   29%
   30%  --- run(CP,H,H2): H2 is a possible extension of H by executing CP
   31%
   32% The following predicates are required:
   33%  --- prim_action(action) - for each primitive action
   34%  --- poss(action,cond)   - when cond holds, action is executable
   35%  --- sensing(A,VL) - VL is a list of possible sensing values of action A
   36%
   37%  --- simulator(Id,C,A) : Under simulator Id, exog action A must happens if C holds (optional)
   38%  --- inconsistent(H) - last action make history H inconsistent
   39%  --- restrict_actions(Name,Goal,N,AA,C,NA) - 
   40%                 In the planning Name, when C holds, restrict to 
   41%                 actions in NA when planning for Goal at the Nth level 
   42%                 with initial set of actions AA
   43%       To achieve no Filtering: restrict_actions(name,_,_,_,false,_). 
   44%                       
   45%  --- eval(P,H,B):  B is the truth value of P at history H (MAIN PREDICATE)
   46%  --- handle_sensing(A,H,Sr,H2): alter the history H to encode the sensing 
   47%                                 result of action A at H
   48%  --- fix_term(A): fix all of some of the variables in A (optional)
   49%					used with theories with constraints
   50%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   51:- dynamic simulator/3,          % These predicates may be not defined
   52           fix_term/1,
   53           restrict_actions/6. 
   54
   55%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   56%  The planner (extended)
   57% Differences with the original version:
   58%    1) change good_state/3 for the more general restrict_actions/5
   59%    2) simulate exogenous action after each step using user provided
   60%       exogenous action simulator via simulator/3
   61%    3) sensing handled more general by using handle_sensing/3 depending
   62%       on what theory of action is used
   63%    4) inconsistent situations is now handle via type-theory inconsistent/1 
   64%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 wscp(+Name, +Goal, +Max, +LAct, +InitState, -Plan)
Top-level planner predicate wscp/5 wscp/7 --- Name id of the planning process type (used for forward filtering) --- Goal is the condition to planfor --- Max is the maximum level allowed --- InitState is the initial history we start on --- Plan is the computed (output) plan --- LOptions is the list of options:

wscp/5 Assumes no exogenous action simulator and all actions allowed wscp/7 Uses the exogenous action simulator with id SimId

   82wscp(Name,Goal,Max,InitState,Plan,LOptions) :-	% THE MAIN RULE
   83	extract_option(LOptions,simid,SimId,none), 
   84	extract_option(LOptions,actions,LAct,_AnyLAct), 
   85	idplan(Name,Goal,0,Max,InitState,Plan,LAct,SimId).
   86
   87
   88% Iterative deeping planner (on top of depth-search dfplan/7)
   89idplan(Name,Goal,N,_Max,InitState,Plan,LAct,SimId) :- 
   90	dfplan(Name,Goal,N,InitState,Plan,LAct,SimId).
   91idplan(Name,Goal,N,Max,InitState,Plan,LAct,SimId) :- 
   92	N < Max, N1 is N+1, 
   93	idplan(Name,Goal,N1,Max,InitState,Plan,LAct,SimId).
   94
   95
   96% Depth-first planner for Goal, up to depth level N
   97% Simulated actions are "added" to both the situation S and the Plan
   98% Usually, simulated actions will be stated via the sim(_) construct
   99dfplan(_Name,Goal,_N,S,[],_LAct,_SimId) :- holds_wscp(Goal,S). 
  100dfplan(Name,Goal,N,S,Plan,LAct,SimId) :- N > 0, 
  101    filter(Name,Goal,N,LAct,S,LAct2), LAct2\=[], % Actions forward filtering
  102    simulate_exog(S,SimId,SE), 
  103    append(SE,S,S2),	% Add simulated actions to the current situation 
  104    append(SE,Plan2,Plan),	% Add simulated actions to plan
  105    prim_action(A), allowed(A,LAct2),	% Pick an allowed action 
  106    poss(A,C2), holds_wscp(C2,S2), 
  107    (fix_term(A) -> true ; true),    % Ground the action A if possible
  108    N1 is N-1, 
  109    try_action(Name,Goal,N1,S2,A,Plan2,LAct,SimId).
  110  
  111% Try sensing action A at level N
  112try_action(Name,Goal,N,S,A,[A,case(A,BL)],AA,SimNo) :- 
  113               sensing(A,VL), !, build_ifs(Name,Goal,N,S,A,VL,BL,AA,SimNo).
  114% Try non-sensing action A at level N
  115try_action(Name,Goal,N,S,A,[A|RPlan],AA,SimNo)      :- 
  116               dfplan(Name,Goal,N,[A|S],RPlan,AA,SimNo).
  117
  118% Build case structure using the list [V|VL] of sensing results for A
  119build_ifs(_,_,_,_,_,[],[],_,_).
  120build_ifs(Name,Goal,N,S,A,[V|VL],[if(V,Plan)|BL],AA,SimNo) :-
  121	handle_sensing(A,[A|S],V,S2),
  122	( inconsistent(S2) -> Plan=[inc] ; 
  123                              once(dfplan(Name,Goal,N,S2,Plan,AA,SimNo)) ),
  124	build_ifs(Name,Goal,N,S,A,VL,BL,AA,SimNo).
  125
  126% Perform the forward filtering. LAct3 is the new set of possible actions
  127filter(Name,Goal,N,LAct,S,LAct3):- 
  128	restrict_actions(Name,Goal,N,LAct,C1,LAct2), !,
  129	(holds_wscp(C1,S) -> LAct3=LAct2 ; LAct3=LAct2).
  130filter(_,_,_,LAct,_,LAct).        % No forward filtering
  134allowed(A,AA):- \+ \+ member(A,AA), !.
Given situation S, and exog. simulator with id SimId, S2 will be the next situation with all simulated exogenous actions included
  140simulate_exog(S,SimId,[A|SE]):- 
  141	ground(SimId), 
  142	SimId\=none,
  143	simulator(SimId,C,A), holds_wscp(C,S), !,
  144	simulate_exog([A|S],SimId,SE).
  145simulate_exog(_,_,[]).	% no action simulated
  146
  147
  148% WSCP only considers true projection. Ignore false or unknowns.
  149holds_wscp(C,H):- eval(C,H,true).
  150
  151%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  152%  Plan & Print plan (Name is the name of the planning problem)
  153% pplan(Name,Goal,Max)    : plan for Goal up to Max depth
  154% pplan(Name,Goal,Max,End): plan for Goal up to Max depth. At the end print
  155%                   the plan using End as the final condition to print out
  156%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  157pplan(Goal,Max)      :- pplan(Goal, Goal,Max,true).  % Make Name=Goal
  158pplan(Name,Goal,Max) :- pplan(Name,Goal,Max,true).
  159pplan(Name,Goal,Max,End) :- wscp(Name,Goal,Max,[],Plan), nl, 
  160	write('Planning name is '), write(Name), nl,
  161	write('Goal is '), write(Goal), nl, nl, pp(0,Plan,[],End), nl.
  162
  163%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  164%  pp(I,Plan,S,E): Pretty print of a plan Pt
  165%         - I is the initial indentation
  166%         - Plan is the plan to print
  167%         - S is the initial situation
  168%         - E is the final condition to print out
  169%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  170pp(_,[],_,true) :- !.
  171pp(N,[],S,End) :- subf(End,P,S), tab(N), write('*** '), call(P), nl.
  172pp(N,[case(A,L)],S,End) :- !, tab(N), 
  173	write(A), nl, N2 is N+1, pp2(N2,L,A,S,End).
  174pp(N,[A|L],S,End) :- !, tab(N), write(A), nl, pp(N,L,[A|S],End).
  175
  176pp2(_,[],_,_,_).
  177pp2(N,[if(V,P)|L],A,S,End) :- tab(N), write(V), write(' => '), nl, N2 is N+1, 
  178	pp(N2,P,[e(_,V)|S],End), pp2(N,L,A,S,End).
  179
  180
  181
  182
  183%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  184%  run/3 extracts each potential history-path in a conditional plan 
  185%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  186% H is a potential history after executing the CPP 
  187% (i.e, H is a history after executing "some" branch in CPP)
  188run(CPP,H):- run(CPP,[],H).
  189run([],H,H).
  190run([A,case(A,BL)],H,H3):-!, member(if(V,PV),BL), 
  191                          handle_sensing(A,[A|H],V,H2), 
  192			  run(PV,H2,H3).
  193run([A|R],H,H2):- run(R,[A|H],H2).
  194
  195% FL is the length (i.e, number of actions) of history H
  196% FL is the real length minus the number of sensing results in H
  197hist_length(H,N):- findall(A, (member(A,H), prim_action(A)),LA),
  198	           length(LA,N).
  199
  200%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  201% EOF: Interpreters/wscplan.pl
  202%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%