/*			APPENDIX  B
		Section B.3   Motivating Examples
	B.3.1   Axioms for examples that illustrate backtracking.
*/
:- set_flag(all_dynamic, on). 
:- dynamic(proc/2).

/* GOLOG Procedures */

proc(goto(L,T),
  pi(rloc,?(robotLocation(rloc)) : pi(deltat,?(travelTime(rloc,L,deltat)) :
     goBetween(rloc,L,deltat,T)))).

proc(goBetween(Loc1,Loc2,Delta,T),
   ?(Loc1=Loc2 & Delta=0) # 
          ?(-(Loc1=Loc2) & Delta > 0) : startGo(Loc1,Loc2,T) :
   pi(t, ?(t $= T + Delta) : endGo(Loc1,Loc2,t)) ).

/* Preconditions for Primitive Actions */

poss(pickupCoffee(T),S) :- not holdingCoffee(S), robotLocation(cm,S), 
                   start(S,TS),  TS $<= T.

poss(giveCoffee(Person,T),S) :- holdingCoffee(S),
                                robotLocation(office(Person),S),
                                start(S,TS), TS $<= T.

poss(startGo(Loc1,Loc2,T),S) :- not going(L,LL,S), 
                                robotLocation(Loc1,S),
                                start(S,TS), TS $<= T.

poss(endGo(Loc1,Loc2,T),S) :- going(Loc1,Loc2,S),
                                start(S,TS), TS $<= T.


/* Successor State Axioms */

hasCoffee(Person,do(A,S)) :- A = giveCoffee(Person,T) ;
                             hasCoffee(Person,S).

robotLocation(Loc,do(A,S)) :- A = endGo(Loc1,Loc,T) ;
                      ( robotLocation(Loc,S),  
                       not A = endGo(Loc2,Loc3,T) ).

going(Loc1,Loc2,do(A,S)) :- A = startGo(Loc1,Loc2,T) ;
                                   (going(Loc1,Loc2,S),
                                    not A = endGo(Loc1,Loc2,T)).

holdingCoffee(do(A,S)) :- A = pickupCoffee(T) ;
                                (holdingCoffee(S),
                                 not A = giveCoffee(Person,T)).

util(0, s0).
util(V2, do(giveCoffee(Person,T),S)) :- util(V, S), 
             wantsCoffee(Person,T1,T2), not hasCoffee(Person,S),
               V1 $<= (T2 - T)/2, 
              V1 $<= T - (3*T1 - T2)/2 , 
              V2 $= 700 - T + V + V1*11/10.
               
util(V, do(A,S)) :- A \=giveCoffee(P,T), util(V, S).

/* The time of an action occurrence is its last argument. */

time(pickupCoffee(T),T).       
time(giveCoffee(Person,T),T).
time(startGo(Loc1,Loc2,T),T).  
time(endGo(Loc1,Loc2,T),T).

/* Restore situation arguments to fluents. */

restoreSitArg(robotLocation(Rloc),S,robotLocation(Rloc,S)).
restoreSitArg(hasCoffee(Person),S,hasCoffee(Person,S)).
restoreSitArg(going(Loc1,Loc2),S,going(Loc1,Loc2,S)).
restoreSitArg(holdingCoffee,S,holdingCoffee(S)).

/* Primitive Action Declarations */

primitive_action(pickupCoffee(T)).
primitive_action(giveCoffee(Person,T)).
primitive_action(startGo(Loc1,Loc2,T)).
primitive_action(endGo(Loc1,Loc2,T)).


travelTime(L,L,0).
travelTime(L1,L2,T) :- travelTime0(L1,L2,T) ;
                       travelTime0(L2,L1,T).

travelTime0(cm,office(sue),15).
travelTime0(cm,office(mary),10).
travelTime0(cm,office(bill),8).
travelTime0(cm,office(joe),10).
travelTime0(office(bill),office(sue),18).
travelTime0(office(bill),office(mary),15).
travelTime0(office(sue),office(mary),5).

drive( StartPos, EndPos ) :- nl, write("drive, drive, drive from "), 
                             write(StartPos), write(" to "), write(EndPos), nl.

/*
The file ``simul'' is the wrapper that calls the golog interpreter,
the monitor of temporal programs, the file ``coffee'' that defines
the application and the file ``exec'' that includes auxilary predicates.

:- [ 'golog' ].
:- [ 'moni' ].
:- [ 'coffee' ].          % calls  hli_go_path()
:- [ 'exec' ].        
:- set_flag(recover/7, spy, on).
:- set_flag(recover/7, leash, stop).  

run :-     online( deliverCoffee(2), empty, s0, LastSit ), 
           schedMin(s0, LastSit),
           nl, write(">> The last situation is "), 
                 write(LastSit), !, nl.
 
run :-     printf( "Sorry, something is wrong...\n", [] ),
            flush( output ).

visit1 :-  online( visit1, empty, s0, Sfin).
visit2 :-  online( visit2, empty, s0, Sfin).
visit3 :-  online( visit3, empty, s0, Sfin).
*/
/*
dvp.cs> eclipse -b simul
structures.pl compiled traceable 3764 bytes in 0.03 seconds
suspend.pl compiled traceable 8012 bytes in 0.13 seconds
r.sd       loaded traceable 61220 bytes in 0.48 seconds
fromonto.pl compiled traceable 3304 bytes in 0.01 seconds
golog      compiled traceable 19856 bytes in 0.62 seconds
moni       compiled traceable 13668 bytes in 0.06 seconds
coffee     compiled traceable 45472 bytes in 0.13 seconds
exec       compiled traceable 5000 bytes in 0.04 seconds
simul      compiled traceable 980 bytes in 0.88 seconds
ECRC Common Logic Programming System [sepia opium megalog parallel]
Version 3.5.2, Copyright ECRC GmbH, Wed Jan  3 12:54 1996
[eclipse 1]: visit2.
lists.pl   compiled traceable 8200 bytes in 0.04 seconds


>> action startGo(office(joe), cm, 91) is planned for execution

>> Enter: current time.
	91.
>> The current time is 91
 runAction is working

>> Im doing the action startGo(office(joe), cm, 91) at time 91
  *-> start going from office(joe) to cm

drive, drive, drive from office(joe) to cm

>> action endGo(office(joe), cm, 101) is planned for execution

>> Enter: current time.
	120.
>> The current time is 120
>> RELEVANT is working ...


>> RECOVER1 is working...

>> RECOVER1 is working...

>> RECOVER1 is working...

>> RECOVER1 is working...

>> RECOVER1 is working...

>> RECOVER1 is working...

>> RECOVER1 is working...

>> RECOVER1 is working...

>> RECOVER2 is working...

>> RECOVER2 is working...

>> RECOVER2 is working...

>> RECOVER2 is working...

>> RECOVER2 is working...

>> RECOVER2 is working...

>> RECOVER2 is working...

>> Do endGo(office(joe), cm, 120) , but skip subsequent actions

 runAction is working

>> Im doing the action endGo(office(joe), cm, 120) at time 120
  *-> end going from office(joe) to cm

>> action pickupCoffee(120) is planned for execution

>> Enter: current time.
	121.
>> The current time is 121
>> RELEVANT is working ...

 runAction is working

>> Im doing the action pickupCoffee(121) at time 121
  *-> give some coffee please

>> action startGo(cm, office(mary), 121) is planned for execution

>> Enter: current time.
	122.
>> The current time is 122
>> RELEVANT is working ...

 runAction is working

>> Im doing the action startGo(cm, office(mary), 122) at time 122
  *-> start going from cm to office(mary)

drive, drive, drive from cm to office(mary)

>> action endGo(cm, office(mary), 132) is planned for execution

>> Enter: current time.
	133.
>> The current time is 133
>> RELEVANT is working ...

 runAction is working

>> Im doing the action endGo(cm, office(mary), 133) at time 133
  *-> end going from cm to office(mary)

yes.
*/