1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2% FILE    : Interpreters/transfinal-congolog.pl
    3%
    4%       IndiGolog TRANS & FINAL Implementation for the ConGolog language.
    5%
    6%  AUTHOR : Sebastian Sardina 
    7%           based on the definitions for ConGolog by 
    8%			Giuseppe De Giaccomo, Yves Lesperance, and Hector Levesque
    9%  EMAIL  : ssardina@cs.toronto.edu
   10%  WWW    : www.cs.toronto.edu/~ssardina www.cs.toronto.edu/cogrobo
   11%  TYPE   : system independent code
   12%  TESTED : SWI Prolog 5.0.10 http://www.swi-prolog.org
   13%
   14%           For more information on Golog and some of its variants, see:
   15%               http://www.cs.toronto.edu/~cogrobo/
   16%
   17%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   18%
   19%  This file provides:
   20%
   21% -- trans(P,H,P2,H2)    : configuration (P,H) can perform a single step
   22%                          to configuration (P2,H2)
   23% -- final(P,H)          : configuration (P,H) is terminating
   24%
   25%  The following special features are also provided:
   26% 
   27% -- A special action `wait' that is always possible. It can be used to state 
   28%         that the program will be waiting for an exogenous action.
   29% -- A special action `stop_interrupts' that is used to set the fluent
   30%         interrupts_running to false
   31% -- A special fluent `interrupts_running' that is always true unless stopped
   32%
   33%
   34%  The following is required for this file:
   35%
   36% FROM SYSTEM CODE DEPENDING ON WHERE IT IS USED
   37% -- report_message(T, M) : report message M of type T
   38%
   39% FROM TEMPORAL PROJECTOR:
   40% -- isTrue(+C, +H) 
   41%           Conditio C is true at history H
   42% -- calc_arg(+A, -A2, +H) 
   43%           calculate the arguments of action A at history H
   44% -- domain(-V, +D)       
   45% -- rdomain(-V, +D)       
   46%           object V is an element of domain D (random)
   47% -- getdomain(+D, -L) 
   48%           L is the list of elements in domain D
   49% -- sensed(+A, ?V, ?H) 
   50%           action A got sensing result V w.r.t. history H
   51%
   52% FROM DOMAIN SPECIFIC CODE:
   53% -- prim_action(action) : for each primitive action 
   54% -- exog_action(action) : for each exogenous action 
   55% -- poss(action,cond)   : precondition axioms
   56%
   57%  Code for describing the high-level program:
   58% -- proc(name,P)           : for each procedure P 
   59% -- simulator(Id,C,A)      : Under simulator Id, exog action A must happens if C holds
   60%
   61% OTHERS (PROLOG SPECIFIC):
   62% -- false
   63%            equivalent to fail
   64% -- random(+L,+U,-R) 
   65%            randomly returns a number R between L and U
   66% -- subv(+X1,+X2,+T1,-T2) 
   67%            T2 is T1 with X1 replaced by X2
   68% -- catch/3 and throw/1 for handling exceptions 
   69%            (provide empty implementations of both if there is no support 
   70%            for exceptions available)
   71% -- shuffle/2 : shuffle a list into another list in a random way
   72%
   73% -- call_with_time_limit(+Sec, +Goal): True if Goal completes within Time. 
   74%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   75
   76%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   77%                            TRANS and FINAL                           
   78% Trans(E,H,E1,H1) ->  One execution step of program E from history H  
   79%			 leads to program E1 with history H1.           
   80% Final(E,H)       ->  Program E at history H is final.                
   81%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   82
   83
   84    /* CONGOLOG CONSTRUCTS                                           */
   85    /*    iconc(E)    : iterative concurrent execution of E              */
   86    /*    conc(E1,E2) : concurrent (interleaved) execution of E1 and E2  */
   87    /*    pconc(E1,E2): prioritized conc. execution of E1 and E2 (E1>E2) */
   88    /*    bpconc(E1,E2,H): used to improve the performance of pconc(_,_) */
   89    /*                                                                   */
   90final(iconc(_),_).
   91final(conc(E1,E2),H)  :- final(E1,H), final(E2,H).
   92final(pconc(E1,E2),H) :- final(E1,H), final(E2,H).
   93trans(iconc(E),H,conc(E1,iconc(E)),H1) :- trans(E,H,E1,H1).
   94
   95trans(conc(E1,E2),H,conc(E,E2),H1) :- trans(E1,H,E,H1).
   96trans(conc(E1,E2),H,conc(E1,E),H1) :- trans(E2,H,E,H1).
   97trans(pconc(E1,E2),H,E,H1) :-    % bpconc(E1,E2,H) is for when E1 blocked at H
   98    trans(E1,H,E3,H1) -> E=pconc(E3,E2) ; trans(bpconc(E1,E2,H),H,E,H1).
   99
  100% bpconc(E1,E2,H) does not reconsider process E1 as long as the history
  101% remains being H (at H, E1 is already known to be blocked)
  102trans(bpconc(E1,E2,H),H,E,H1) :- !,
  103    trans(E2,H,E3,H1),  % blocked history H
  104    (H1=H -> E=bpconc(E1,E3,H) ; E=pconc(E1,E3)).
  105trans(bpconc(E1,E2,_),H,E,H1) :- trans(pconc(E1,E2),H,E,H1).
  106
  107
  108       /* INTERRUPTS */
  109trans(interrupt(Trigger,Body),H,E1,H1) :-
  110    trans(while(interrupts_running,if(Trigger,Body,?(neg(true)))),H,E1,H1).
  111
  112trans(interrupt(V,Trigger,Body),H,E1,H1) :- 
  113    trans(while(interrupts_running, 
  114    		pi(V,if(Trigger,Body,?(neg(true))))),H,E1,H1).  
  115
  116final(interrupt(Trigger,Body),H) :-
  117    final(while(interrupts_running,if(Trigger,Body,?(neg(true)))), H).
  118
  119final(interrupt(V,Trigger,Body),H) :- 
  120    final(while(interrupts_running, pi(V,if(Trigger,Body,?(neg(true))))),H).
  121
  122% Note these fluents (e.g., halt) and special actions (e.g., halt_exec) need to be defined already.
  123trans(prioritized_interrupts(L),H,E1,H1) :- 
  124    expand_interrupts([interrupt(haveExecuted(halt),  halt_exec),
  125    		       interrupt(haveExecuted(abort), abort_exec),
  126    		       interrupt(haveExecuted(pause), break_exec),
  127    		       interrupt(haveExecuted(reset), reset_exec),
  128		       interrupt(haveExecuted(debug), debug_exec)|L],E), !,
  129    trans(E,H,E1,H1).
  130
  131trans(prioritized_interrupts_simple(L),H,E1,H1) :- 
  132%    expand_interrupts([interrupt(haveExecuted(halt),halt_exec)|L],E), !,
  133    expand_interrupts(L,E), !,
  134    trans(E,H,E1,H1).
  135
  136expand_interrupts([],stop_interrupts).
  137
  138expand_interrupts([X|L],pconc(X,E)) :-
  139    expand_interrupts(L,E).
  140
  141% trans and final for system actions (e.g., show_debug, halt_exec, etc.)    
  142trans(stop_interrupts,H,[],[stop_interrupts|H]).
  143final(stop_interrupts,_) :- fail, !.
  144
  145
  146
  147    /* GOLOG CONSTRUCTS                                           */
  148    /*                                                                */
  149    /*  These include primitive action, test, while, pick, if         */
  150    /*  nondeterministic choice and nondeterministic iteration.	      */
  151    /*								      */
  152final([],_).
  153final(star(_),_).
  154final(star(_,_),_).
  155final([E|L],H)       :- final(E,H), final(L,H).
  156final(ndet(E1,E2),H) :- final(E1,H) ; final(E2,H).
  157final(if(P,E1,E2),H) :- ground(P), !, (isTrue(P,H) -> final(E1,H) ; final(E2,H)).
  158final(if(P,E1,_),H)  :- isTrue(P,H), final(E1,H).
  159final(if(P,_,E2),H)  :- isTrue(neg(P),H), final(E2,H).
  160final(while(P,E),H)  :- isTrue(neg(P),H) ; final(E,H).
  161
  162final(pi([],E),H)    :- !, final(E,H).
  163final(pi([V|L],E),H) :- !, final(pi(L,pi(V,E)),H).
  164final(pi(V,E),H)     :- !, subv(V,_,E,E2), !, final(E2,H).
  165final(pi((V,D),E),H) :- !, final(pi(V,D,E),H).
  166final(pi(V,D,E),H)   :- domain(W,D), subv(V,W,E,E2), !, final(E2,H).
  167
  168final(E,H)           :- proc(E,E2), !, final(E2,H).
  169
  170
  171
  172trans([E|L],H,E1,H2)      :- \+ L=[], final(E,H), trans(L,H,E1,H2).
  173trans([E|L],H,[E1|L],H2)  :- trans(E,H,E1,H2).
  174trans(?(P),H,[],H)        :- isTrue(P,H).
  175trans(ndet(E1,E2),H,E,H1) :- trans(E1,H,E,H1) ; trans(E2,H,E,H1).
  176trans(if(P,E1,E2),H,E,H1) :- ground(P), !,
  177	(isTrue(P,H) -> trans(E1,H,E,H1) ;  trans(E2,H,E,H1)).
  178trans(if(P,E1,E2),H,E,H1)  :- !,
  179	((isTrue(P,H), trans(E1,H,E,H1)) ; (isTrue(neg(P),H), trans(E2,H,E,H1))).
  180trans(star(E,1),H,E1,H1)  :- !, trans(E,H,E1,H1).
  181trans(star(E,N),H,[E1,star(E,M)],H1)   :- N>1, trans(E,H,E1,H1), M is N-1.
  182trans(star(E),H,E1,H1)       :- trans(E,H,E1,H1).
  183trans(star(E),H,[E1,star(E)],H1)       :- trans(E,H,E1,H1).
  184trans(while(P,E),H,[E1,while(P,E)],H1) :- isTrue(P,H), trans(E,H,E1,H1).
  185
  186trans(pi([],E),H,E1,H1)    :- !, trans(E,H,E1,H1).
  187trans(pi([V|L],E),H,E1,H1) :- !, trans(pi(L,pi(V,E)),H,E1,H1).
  188trans(pi((V,D),E),H,E1,H1) :- !, trans(pi(V,D,E),H,E1,H1).
  189trans(pi(r(V),D,E),H,E1,H1):- !, rdomain(W,D), subv(V,W,E,E2), trans(E2,H,E1,H1).
  190trans(pi(V,D,E),H,E1,H1)   :- !, domain(W,D), subv(V,W,E,E2), trans(E2,H,E1,H1).
  191trans(pi(V,E),H,E1,H1)     :- subv(V,_,E,E2), !, trans(E2,H,E1,H1).
  192
  193
  194%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  195% LAST TRANS FOR PROCEDURES AND PRIMITIVE ACTIONS (everything else failed)
  196% Replace the arguments by their value, check that it is a primitive action
  197% and finally check for preconditions.
  198%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  199trans(E,H,E1,H1)    :- proc(E,E2), !, trans(E2,H,E1,H1).
  200trans(A,H,[],[A|H]) :- system_action(A), !.
  201final(A,_) 	    :- system_action(A), !, fail.
  202
  203trans(E,H,[],[E1|H])    :- 
  204	calc_arg(E,E1,H),
  205	prim_action(E1), 
  206	poss(E1,P), 
  207	isTrue(P,H).
  208
  209
  210
  211
  212%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  213% EOF: Interpreters/transfinal-congolog.pl
  214%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%