1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2% FILE    : Interpreters/transfinal-ext.pl
    3%
    4%       IndiGolog TRANS & FINAL Implementation for 
    5%			some extended constructs to the ConGolog language.
    6%
    7%  AUTHOR : Sebastian Sardina 
    8%           based on the definitions for ConGolog by 
    9%			Giuseppe De Giaccomo, Yves Lesperance, and Hector Levesque
   10%  EMAIL  : ssardina@cs.toronto.edu
   11%  WWW    : www.cs.toronto.edu/~ssardina www.cs.toronto.edu/cogrobo
   12%  TYPE   : system independent code
   13%  TESTED : SWI Prolog 5.0.10 http://www.swi-prolog.org
   14%
   15%           For more information on Golog and some of its variants, see:
   16%               http://www.cs.toronto.edu/~cogrobo/
   17%
   18%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   19%
   20%  This file provides:
   21%
   22% -- trans(P,H,P2,H2)    : configuration (P,H) can perform a single step
   23%                          to configuration (P2,H2)
   24% -- final(P,H)          : configuration (P,H) is terminating
   25%
   26%  The following special features are also provided:
   27% 
   28%
   29%
   30%  The following is required for this file:
   31%
   32% FROM SYSTEM CODE DEPENDING ON WHERE IT IS USED
   33% -- report_message(T, M) : report message M of type T
   34%
   35% FROM TEMPORAL PROJECTOR:
   36% -- isTrue(+C, +H) 
   37%           Conditio C is true at history H
   38% -- calc_arg(+A, -A2, +H) 
   39%           calculate the arguments of action A at history H
   40% -- domain(-V, +D)       
   41% -- rdomain(-V, +D)       
   42%           object V is an element of domain D (random)
   43% -- getdomain(+D, -L) 
   44%           L is the list of elements in domain D
   45% -- sensed(+A, ?V, ?H) 
   46%           action A got sensing result V w.r.t. history H
   47%
   48%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   49
   50
   51
   52%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   53%                            TRANS and FINAL                           
   54% Trans(E,H,E1,H1) ->  One execution step of program E from history H  
   55%			 leads to program E1 with history H1.           
   56% Final(E,H)       ->  Program E at history H is final.                
   57%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   58
   59    /* (A) EXTENDED CONSTRUCTS                                           	*/
   60    /*    wndet(E1,E2) : Weak nondeterministic choice of program         	*/
   61    /*    rndet(E1,E2) : Real nondeterministic choice of program	 		*/
   62    /*    rconc(E1,E2) : Real concurrency on 2 programs   	    	 		*/
   63    /*    rconc(L) 	   : Real concurrency on a list of programs L 	 		*/
   64    /*    rrobin(L)	   : Round-robin concurrency		 					*/	
   65    /*    rpi(X,D)     : Real nondeterministic choice of argument from D 	*/
   66    /*    gexec(P,E)   : Guarded execution of program E wrt condition P  	*/
   67    /*    goal(PSucc,E,PFail,ERec): full guarded execution		 			*/
   68    /*    abort(P)     : Abort process identified with P                 	*/
   69    /*    ??(P)        : Like ?(P) but it leaves a test(P) mark in H     	*/
   70    /*    wait         : Meta action to wait until an exogenous event    	*/
   71    /*    commit       : Meta action to commit to the plan found so far  	*/
   72    /*    abort        : Meta action to, suddenly,  abort execution      	*/
   73    /*	  time(P,Sec)  : Make first step on P in less than Sec seconds	 	*/
   74    /*	  ttime(P,Sec) : Make every step on P in less than Sec seconds 	 	*/
   75% Try to execute program E1 first. If impossible, then try program E2 instead
   76trans(wndet(E1,E2),H,E,H1) :- trans(E1,H,E,H1) -> true ; trans(E2,H,E,H1).
   77final(wndet(E1,E2),H)      :- final(E1,H), final(E2,H).
   78%final(wndet(E1,E2),H)      :- final(E1,H) ; (\+ trans(E1,H,_,H), final(E2,H)).
   79
   80% Simulate random choice in a nondeterministc choice of programs
   81trans(rndet(E1,E2),H,E,H1):- 
   82        random(1,10,R), % flip a coin!
   83	(R>5 -> (trans(E1,H,E,H1) ; trans(E2,H,E,H1)) ;
   84	        (trans(E2,H,E,H1) ; trans(E1,H,E,H1)) ).
   85final(rndet(E1,E2),H):- final(E1,H) ; final(E2,H).
   86
   87% Simulate random choice in a concurrent execution of E1 and E2
   88trans(rconc(E1,E2),H,rconc(E11,E22),H1) :- 
   89    (random(1, 3, 1) -> 	% flip a coin!
   90    	( (trans(E1,H,E11,H1), E22=E2) ; (trans(E2,H,E22,H1), E11=E1) ) 
   91    	;
   92        ( (trans(E2,H,E22,H1), E11=E1) ; (trans(E1,H,E11,H1), E22=E2) ) 
   93    ).
   94trans(rconc(L),H,rconc([E1|LRest]),H1) :-
   95	length(L,LL),
   96	random(0,LL, R),
   97	nth0(R,L,E),
   98	trans(E,H,E1,H1),
   99	select(E,L,LRest).	 
  100final(rconc(E1,E2),H) :- final(conc(E1,E2),H).
  101final(rconc([]),_).
  102final(rconc([E|L]),H) :- final(E,H), final(rconc(L),H).
  103
  104trans(rrobin(L),H,rrobin(L2),H1) :-
  105	select(E,L,LRest),
  106	trans(E,H,E1,H1),
  107	append(LRest,[E1],L2).
  108final(rrobin(L),H) :- final(rconc(L),H).
  109
  110
  111% Execute E atomically (i.e., as a transaction)
  112trans(atomic(E),H,[],[atomic(E2)|H2]) :-
  113	trans(E,H,E2,H2).
  114final(atomic(E),H) :- final(E,H).
  115
  116
  117% Execute program E as long as condition P holds; finish E if neg(P) holds
  118final(gexec(_,E), H) :- final(E,H).
  119trans(gexec(P,E), H, gexec2(P,E1), H1) :- 	% P needs to be a simple fluent
  120        assume(P, true, H, H2),    % Set P to be TRUE
  121        trans(E, H2, E1, H1).
  122final(gexec2(P,E), H) :- isTrue(neg(P),H) ; final(E,H).
  123trans(gexec2(P,E), H, gexec2(P,E1), H1) :- isTrue(P,H), trans(E,H,E1,H1).
  124
  125
  126% goal(PSucc,E,PFail,ERec): full guarded execution
  127%	PSucc 	: finalize successfully if PSucc holds
  128%	E	: the program to be executed
  129%	PFail	: Terminate the program E and execute recovery procedure ERec
  130final(goal(PSucc,E,_,_), H) :- isTrue(PSucc,H) ; final(E,H).
  131trans(goal(PSucc,_,PFail,ERec), H, E2, H2) :-
  132	isTrue(neg(PSucc),H),
  133	isTrue(PFail,H),
  134	trans(ERec,H, E2, H2).
  135trans(goal(PSucc,E,PFail,ERec), H, goal(PSucc,E2,PFail,ERec), H2) :-
  136	isTrue(neg(PSucc),H),
  137	isTrue(neg(PFail),H),
  138	trans(E,H,E2,H2).
  139
  140% Abort process identified with P by setting P to false in H
  141trans(abort(P), H, [], H1) :- assume(P, false, H, H1).
  142
  143% Perform program P(V) with all elements in domain D: P(e1);P(e2);...;P(en)
  144% Domain D can either be a list of elements or a domain identifier from 
  145% where we get its domain list with getdomain/2
  146trans(for(V,D,P),H,E1,H1) :- D\=[], atom(D), !, getdomain(D,L), 
  147                             trans(for(V,L,P),H,E1,H1).
  148trans(for(V,[F|L],P),H,[E1,for(V,L,P)],H1) :- 
  149	subv(V,F,P,P1), trans(P1,H,E1,H1).
  150
  151final(for(V,D,P),H)    :- D\=[], atom(D), !, getdomain(D,L), 
  152                          final(for(V,L,P),H).
  153final(for(_,[],_),_).
  154final(for(V,[F|L],P),H):- subv(V,F,P,P1), final(P1,H), final(for(V,L,P),H).
  155
  156% A test action that leaves a mark in the history
  157trans(??(P),H,[],[test(P)|H]):- isTrue(P,H). 
  158
  159% Simulation of exogenous actions E
  160trans(sim(E),H,[],[sim(E)|H]):- !, calc_arg(E,E1,H), exog_action(E1).
  161
  162% Wait and commit are two "meta" actions.
  163% wait action tells the interpreter to wait until an exogenous action arrives
  164% commit is used in search and searchc to commit to the plan computed so far
  165trans(wait,H,[],[wait|H])    :- !. % wait is a no-op but encourages rolling db
  166trans(commit,S,[],[commit|S]).	   % commit to the plan found so far! 
  167trans(abort,S,[],[abort|S]).	   % completely abort execution
  168
  169
  170% Time bounded steps
  171% time(E,Sec)  : make the *first* step in E before Sec seconds
  172% ttime(E,Sec) : make every step before in E before Sec seconds
  173trans(time(E,Sec),H,E2,H2) :- timeout(trans(E,H,E2,H2), Sec, fail).
  174final(time(E,Sec),H) :-	timeout(final(E,H), Sec, fail).
  175trans(ttime(E,Sec),H,time(E2,Sec),H2) :- trans(time(E,Sec),H,E2,H2).
  176final(ttime(E,Sec),H) :- final(time(E,Sec),H).
  177
  178
  179% Perform a transition on E, aborting though if an exogenous action happens
  180% meanwhile and Cond holds in H
  181% requires exog_interruptable/3 from main cycle
  182final(exogint(E,_Cond),H) :- final(E,H).
  183trans(exogint(E,Cond),H,exogint(E2,Cond),H2) :- 
  184	exog_interruptable(trans(E,H,E2,H2), isTrue(Cond,H), Status),
  185	(Status=ok -> 
  186		true 
  187	; 
  188		report_message('TF', system(3),'Computation of trans/4 aborted due to exog events'),
  189		E2=E, H2=H
  190	).
  191
  192
  193%%% Random pick construct
  194trans(rpi([],E),H,E1,H1)   :- !, trans(E,H,E1,H1).
  195trans(rpi([V|L],E),H,E1,H1):- !, trans(rpi(L,rpi(V,E)),H,E1,H1).
  196trans(rpi((V,D),E),H,E1,H1):- !, trans(rpi(V,D,E),H,E1,H1).
  197trans(rpi(V,D,E),H,E1,H1)  :- rdomain(W,D), subv(V,W,E,E2), trans(E2,H,E1,H1).
  198
  199final(rpi([],_,E),H)  :- !, final(E,H).
  200final(rpi([V|L],E),H) :- !, final(rpi(L,rpi(V,E)),H).
  201final(rpi((V,D),E),H) :- !, final(rpi(V,D,E),H).
  202final(rpi(V,D,E),H)   :- rdomain(W,D), subv(V,W,E,E2), !, final(E2,H).
  203
  204
  205trans(?(printHistory),H,[],H) :- !, 
  206	write('CURRENT HISTORY: '), 
  207	writeln(H).
  208	
  209%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  210%% (E) SYNCHRONIZATION CONSTRUCT
  211%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  212%%  Syncronize a set of configuration pairs
  213%%
  214%% trans(sync(EL),H,sync(EL2),H2):
  215%%      programs EL can all perform a syncronized step to EL2 and H2
  216%% final(sync(EL),H):
  217%%      programs EL can all terminate at H
  218%%
  219%% synctrans/4 and syncfinal/2 are a bit more powerful as they may
  220%%  use different situations for the different programs:
  221%%
  222%%    synctrans([E1,E2,...],[H1,H2,...],[E11,E22,...],[H11,H22,...],A)
  223%%  configurations (Ei,Hi) can advance to (Eii,Hii) by doing action A
  224%%    syncfinal([E1,E2,...],[H1,H2,...])
  225%%  configurations (Ei,Hi) can all terminate
  226%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  227trans(sync(LE),H,sync(EL2),[A|H]) :-
  228	length(LE,LL),
  229	buildListRepeat(LL,H,LH),
  230	synctrans(LE,LH,EL2,_,A).
  231
  232final(sync(LE),H) :- 
  233	length(LE,LL),
  234	buildListRepeat(LL,H,LH),
  235	syncfinal(LE,LH).
  236
  237% buildListRepeat(N,E,L) :- L is a list of N repetitions of element E
  238buildListRepeat(0,_,[])    :- !.
  239buildListRepeat(N,H,[H|L]) :- N2 is N-1, buildListRepeat(N2,H,L).
  240
  241synctrans([E],[H],[E2],[A|H],A)   :- !, ttrans(E,H,E2,[A|H]).
  242synctrans([E|LP],[H|LH],[E2|LP2],[[A|H]|LH2],A) :- 
  243	ttrans(E,H,E2,[A|H]), 
  244	synctrans(LP,LH,LP2,LH2,A).
  245
  246syncfinal([E],[H])       :- !, tfinal(E,H).
  247syncfinal([E|LP],[H|LH]) :- tfinal(E,H), syncfinal(LP,LH).
  248
  249
  250%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  251% EOF: Interpreters/transfinal-ext.pl
  252%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%