1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2% FILE    : indigolog-vanilla.pl
    3%
    4%   IndiGolog vanilla interpreter
    5%
    6% First written by Hector Levesque
    7% Modified and adapted by Sebastian Sardina March 1999.
    8% This file contains vanilla Prolog code. If you run in a special Prolog
    9% platform you may want to consult indigolog-vanilla_xxx.pl where xxx is the
   10% corresponding Prolog implementation (e.g., SWI or ECLIPSE)
   11%
   12% This file contains the original IndiGolog interpreter
   13%
   14%   The main tool provided in this file is the following predicate:
   15%
   16% -- indigolog(E):  E is an IndiGolog program
   17%
   18% For more information on Golog and some of its variants, see:
   19%               http://www.cs.toronto.edu/~cogrobo/
   20%
   21%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   22%
   23%
   24%                             March, 1999
   25%
   26% This software was developed by the Cognitive Robotics Group under the
   27% direction of Hector Levesque and Ray Reiter.
   28%
   29%        Do not distribute without permission.
   30%        Include this notice in any copy made.
   31%
   32%
   33%         Copyright (c) 2002-2005 by The University of Toronto,
   34%                        Toronto, Ontario, Canada.
   35%
   36%                          All Rights Reserved
   37%
   38% Permission to use, copy, and modify, this software and its
   39% documentation for non-commercial research purpose is hereby granted
   40% without fee, provided that the above copyright notice appears in all
   41% copies and that both the copyright notice and this permission notice
   42% appear in supporting documentation, and that the name of The University
   43% of Toronto not be used in advertising or publicity pertaining to
   44% distribution of the software without specific, written prior
   45% permission.  The University of Toronto makes no representations about
   46% the suitability of this software for any purpose.  It is provided "as
   47% is" without express or implied warranty.
   48% THE UNIVERSITY OF TORONTO DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS
   49% SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND
   50% FITNESS, IN NO EVENT SHALL THE UNIVERSITY OF TORONTO BE LIABLE FOR ANY
   51% SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER
   52% RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF
   53% CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN
   54% CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
   55% 
   56%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   57%
   58%  In addition to a (Con)Golog program, users provide these predicates:  
   59%
   60%      prim_fluent(fluent),             for each primitive fluent        
   61%      prim_action(action),             for each primitive action        
   62%      exog_action(action),             for each exogenous action        
   63%      senses(action,fluent),           for each sensing action          
   64%      poss(action,cond)                when cond, action is executable  
   65%      initially(fluent,value)          fluent has value in S0           
   66%      causes_val(action,fluent,value,cond)                              
   67%            when cond holds, doing act causes fluent to have value      
   68%
   69%      execute(action,sensing_result)   do the action, return the result 
   70%            can use ask_execute
   71%      exog_occurs(action)              return an exog action            
   72%            can use ask_exog_occurs (or fail, if none)                  
   73%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   74:-dynamic senses/2.   75:-dynamic exog_action/1.   76
   77
   78%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   79%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   80%%%%%%%%%%%%%%%%%%%%%%%%%% MAIN LOOP: indigolog and indixeq %%%%%%%%%%%%%%%%%
   81%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   82%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   83
   84
   85%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   86% indigolog(E): E is a high-level program 
   87% 	The history H is a list of actions (prim or exog), initially [] (empty)
   88% 	Sensing reports are inserted as actions of  the form e(fluent,value)
   89%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   90indigolog(E) :- indigo(E,[]).
   91
   92% (1)- In each single step ask for an exogenous action, check it and 
   93%	continue execution inserting that exogenous action 
   94indigo(E,H) :- 	exog_occurs(Act), exog_action(Act), !, indigo(E,[Act|H]).
   95
   96% (2) - Find a signle step (trans), execute it, commit and continue 
   97indigo(E,H) :- trans(E,H,E1,H1), indixeq(H,H1,H2), !, indigo(E1,H2).
   98
   99% (3) - If E is final write the length of history H 
  100indigo(E,H) :- final(E,H), nl, length(H,N), write(N), write(' actions.'), nl.
  101
  102%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  103% indixeq(H1,H2,H3): Implementation of execution of an action.
  104% 	H1 is the original history, H2 is H1 with the new action to be 
  105%	executed and H3 is the resulting history after executing such new 
  106% 	action. 
  107%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  108% (1) - No action was performed so we dont execute anything 
  109indixeq(H,H,H). 
  110% (2) - The action is not a sensing one: execute and ignore its sensing 
  111indixeq(H,[Act|H],[Act|H]) :- \+ senses(Act,_), execute(Act,_).
  112% (3) - The action is a sensing one for fluent F: execute sensing action
  113indixeq(H,[Act|H],[e(F,Sr),Act|H]) :- senses(Act,F), execute(Act,Sr).
  114
  115
  116%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  117% exog_occurs(Act) and execute(Act,Sr): 
  118% 	predicates that make contact with the outside world.  
  119%	Here are two basic versions using read and write that the domain 
  120%	may use as a simulated environment.
  121%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  122ask_exog_occurs(Act) :- write('Exogenous input:'), read(Act).
  123ask_execute(Act,Sr) :-  write(Act), senses(Act,_) -> (write(':'),read(Sr)); nl.
  124
  125
  126
  127%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  128%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  129%%%%%%%%%%%%%%%%%%%%%%%%%% TRANS and FINAL: lang semantics% %%%%%%%%%%%%%%%%%
  130%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  131%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  132       /* (a) - CONGOLOG */
  133final(conc(E1,E2),H) :- final(E1,H), final(E2,H).
  134final(pconc(E1,E2),H) :- final(E1,H), final(E2,H).
  135final(iconc(_),_).
  136
  137trans(conc(E1,E2),H,conc(E,E2),H1) :- trans(E1,H,E,H1).
  138trans(conc(E1,E2),H,conc(E1,E),H1) :- trans(E2,H,E,H1).
  139trans(pconc(E1,E2),H,E,H1) :- 
  140    trans(E1,H,E3,H1) -> E=pconc(E3,E2) ; (trans(E2,H,E3,H1), E=pconc(E1,E3)).
  141trans(iconc(E),H,conc(E1,iconc(E)),H1) :- trans(E,H,E1,H1).
  142
  143       /* (b) - GOLOG */
  144final([],_).
  145final([E|L],H) :- final(E,H), final(L,H).
  146final(ndet(E1,E2),H) :- final(E1,H) ; final(E2,H).
  147final(if(P,E1,E2),H) :- holds(P,H) -> final(E1,H) ; final(E2,H).
  148final(star(_),_).
  149final(while(P,E),H) :- \+ holds(P,H) ; final(E,H).
  150final(pi(V,E),H) :- subv(V,_,E,E2), final(E2,H).
  151final(E,H) :- proc(E,E2), final(E2,H).
  152
  153trans([E|L],H,[E1|L],H2) :- trans(E,H,E1,H2).
  154trans([E|L],H,E1,H2) :- \+ L=[], final(E,H), trans(L,H,E1,H2).
  155trans(?(P),H,[],H) :- holds(P,H). 
  156trans(ndet(E1,E2),H,E,H1) :- trans(E1,H,E,H1) ; trans(E2,H,E,H1).
  157trans(if(P,E1,E2),H,E,H1) :- holds(P,H) -> trans(E1,H,E,H1) ; trans(E2,H,E,H1).
  158trans(star(E),H,[E1,star(E)],H1) :- trans(E,H,E1,H1).
  159trans(while(P,E),H,[E1,while(P,E)],H1) :- holds(P,H), trans(E,H,E1,H1).
  160trans(pi(V,E),H,E1,H1) :- subv(V,_,E,E2), trans(E2,H,E1,H1).
  161trans(E,H,E1,H1) :- proc(E,E2), trans(E2,H,E1,H1).
  162trans(E,H,[],[E|H]) :- prim_action(E), poss(E,P), holds(P,H).
  163
  164       /* (c) -  SEARCH (ignoring exogenous or other concurrent actions) */
  165/* If (E,H) is a final state then finish. Otherwise, look for a straight
  166   path (E1,L) without looking at exogenous actions */
  167final(search(E),H) :- final(E,H).
  168trans(search(E),H,followpath(E1,L),H1) :- trans(E,H,E1,H1), findpath(E1,H1,L).
  169
  170/* Look for a good path without looking at exogenous actions */
  171findpath(E,H,[E,H]) :- final(E,H).
  172findpath(E,H,[E,H|L]) :- trans(E,H,E1,H1), findpath(E1,H1,L).
  173
  174
  175/* When we have a followpath(E,L), try to advance using the list L
  176   in an offline manner.
  177   If it is not possible to advance any more redo the search to continue */
  178final(followpath(E,[E,H]),H) :- !.
  179final(followpath(E,_),H) :- final(E,H).  /* off path; check again */
  180trans(followpath(E,[E,H,E1,H1|L]),H,followpath(E1,[E1,H1|L]),H1) :- !.
  181trans(followpath(E,_),H,E1,H1) :- trans(search(E),H,E1,H1).  /* redo search */
  182
  183       /* (d) -  INTERRUPTS */
  184prim_action(start_interrupts).
  185prim_action(stop_interrupts).
  186prim_fluent(interrupts).
  187causes_val(start_interrupts, interrupts, running, true).
  188causes_val(stop_interrupts, interrupts, stopped, true).
  189poss(start_interrupts, true).
  190poss(stop_interrupts,  true).
  191
  192proc(interrupt(V,Trigger,Body),            /* version with variable */
  193    while(interrupts=running, pi(V,if(Trigger,Body,?(neg(true)))))).
  194proc(interrupt(Trigger,Body),              /* version without variable */
  195    while(interrupts=running, if(Trigger,Body,?(neg(true))))).
  196proc(prioritized_interrupts(L),[start_interrupts,E]) :- expand_interrupts(L,E).
  197expand_interrupts([],stop_interrupts).
  198expand_interrupts([X|L],pconc(X,E)) :- expand_interrupts(L,E).
  199
  200
  201%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  202%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  203%%%%%%%%%%%%%%%%%%%%%%%%%% HOLDS: temporal projector %%%%%%%%%%%%%%%%%%%%%%%%
  204%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  205%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  206% holds(P,H): formula P is true at history H
  207
  208holds(and(P1,P2),H) :- !, holds(P1,H), holds(P2,H).
  209holds(or(P1,P2),H) :- !, (holds(P1,H) ; holds(P2,H)).
  210holds(neg(P),H) :- !, \+ holds(P,H).   /* Negation by failure */
  211holds(some(V,P),H) :- !, subv(V,_,P,P1), holds(P1,H).
  212holds(P,H) :- proc(P,P1), holds(P1,H).
  213holds(P,H) :- \+ proc(P,P1), subf(P,P1,H), call(P1).
  214
  215       /*  T2 is T1 with X1 replaced by X2  */
  216subv(_,_,T1,T2) :- (var(T1);integer(T1)), !, T2 = T1.
  217subv(X1,X2,T1,T2) :- T1 = X1, !, T2 = X2.
  218subv(X1,X2,T1,T2) :- T1 =..[F|L1], subvl(X1,X2,L1,L2), T2 =..[F|L2].
  219subvl(_,_,[],[]).
  220subvl(X1,X2,[T1|L1],[T2|L2]) :- subv(X1,X2,T1,T2), subvl(X1,X2,L1,L2).
  221
  222       /*  P2 is P1 with all fluents replaced by their values  */
  223subf(P1,P2,_) :- (var(P1);integer(P1)), !, P2 = P1.
  224subf(P1,P2,H) :- prim_fluent(P1), has_val(P1,P2,H).
  225subf(P1,P2,H) :- \+ prim_fluent(P1), P1=..[F|L1], subfl(L1,L2,H), P2=..[F|L2].
  226subfl([],[],_).
  227subfl([T1|L1],[T2|L2],H) :- subf(T1,T2,H), subfl(L1,L2,H).
  228
  229
  230% has_val(F,V,H):  Fluent F has value V in history H.  
  231has_val(F,V,[]) :- initially(F,V).
  232has_val(F,V,[Act|H]) :- sets_val(Act,F,V1,H) -> V = V1 ; has_val(F,V,H).
  233
  234
  235% sets_val(Act,F,V,H): Action Act causes fluent F to be set to V in history H.
  236%		Act can be either an exogenous action e(F,V) or a standard
  237%		action with a successor state axiom causes_val(Act,F,V,P).
  238sets_val(Act,F,V,H) :- Act = e(F,V) ; (causes_val(Act,F,V,P), holds(P,H)).
  239
  240%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  241% EOF: indigolog-vanilla.pl
  242%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%