/*			APPENDIX  B
		Section B.2   An Execution Monitor
*/
/*******************************************************************
   Monitor of Temporal Sequential Golog Programs with Rewards.    
  This requires a Golog interpreter with preferences and rewards.       
 ******************************************************************/
 
/* online(Prog,Trace,S0,Sf):  Sf is the final situation after doing Prog starting
  from S0 where Trace is the sequence of states the program already passed by
  (e.g., when it did non-deterministic branching).   */

online(Delta,H,S,Sf) :-  
        final(Delta,S), Sf=S;
        bestTrans(Delta,S,Delta1,S1),
             %  trans(Delta,S,Delta1,S1), offline(Delta1,S1,Sgoal),
        H1 = trace(Delta,H),
   %     (S1\==S ->  offline(Delta1,S1,Sgoal);  S1==S),
   %     nl, write(">> Delta1= "), write(Delta1), nl,
   %         write(">> BestPlan= "), write(Sgoal), nl,
   %         write(">> Utility= "), util(V,Sgoal), write(V), nl, 
         schedMin(S,S1),     /* Schedule the next action */
           !,              /* do not allow backtracking */
        monitor(S,Delta1,S1,H1,Delta2,S2,H2), 
            !,                    /* do not allow backtracking */
        online(Delta2,H2,S2,Sf).


/*  So far,  no recovery if initial situation is bad */

goalAchievable(Program, S1, Sg) :-
     offline(Program, S1, Sg),   /* Program leads to a goal situation.*/
     schedMin(S1, Sg).           /* and there is a schedule */

/*
schedMin(S1,S1).
schedMin(S1,do(A,S2)) :- 
                 S1==S2,
                 time(A,T), (nonground(T) -> rmin(T); true).
schedMin(S1,do(A,S2)) :- 
                S1\==S2, schedMin(S1,S2), 
                time(A,T), (nonground(T) -> rmin(T); true).
*/

monitor(S,Delta1,S1,Trace1,Delta2,S2,Trace2) :- 
       S == S1,          /* skip tests: they do not have temporal arg*/
       Delta2 = Delta1,
       S2 = S1,
       Trace2 = Trace1.

monitor(S,Delta1,S1,Trace1,Delta2,S2,Trace2) :- 
       S1=do(A, S),      /* find what action is selected for execution */
       nl,
       write(">> action "), write(A), write(" is planned for execution"), 
       nl,
       sense(RealTime, S),    /* watch the current time */
       write(">> The current time is "), write(RealTime), 
       Se=do(watch_time(RealTime),S), 
       time(A, ScheduledTime),
       replaceTime(ScheduledTime, RealTime, Delta1, NewDelta1),
       ( relevant(NewDelta1,S1,Se) -> 
             recover(S1,NewDelta1,Trace1,Se,Delta2,Trace2,S2);
             runAction(A,Se,S2), Delta2=NewDelta1, Trace2 = Trace1 
        ).


/* If action is belated, it should be rescheduled according to a time clock 
  because actions cannot be executed in the past. Note that sensed time 
  may be relevant wrt execution of Delta1 _only if_  action is belated.
  Otherwise, it is sufficient to wait until the time when the action
  was scheduled originally and then do the action in reality.   */

relevant(NewDelta,S1,Se) :-
         S1= do(Action, S),      /* what action has to be done? */
         start(Se, RealTime),
         time(Action, ScheduledTime),
         ScheduledTime < RealTime,
         /* Yes, the action is belated */
         nl, write(">> RELEVANT is working ..."), nl,
         replaceTime(ScheduledTime, RealTime, Action, A),
         !,
         not offline(A : NewDelta, Se, Sg).


replaceTime(OldTime, NewTime, OldPr, NewPr) :-
          sub(OldTime, NewTime, OldPr, Prog) -> NewPr= Prog; 
          NewPr= OldPr.    /* If OldPr does not mention OldTime */

recover(S1,Delta1,History1,Se1,Delta2,History2,S2) :-
       sense(RealTime, Se1),    /* watch the current time */
       write(">> The current time is "), write(RealTime), 
       Se2=do(watch_time(RealTime),Se1), 
   recover1(S1,Delta1,History1,Se2,Delta2,History2,S2) ;
       sense(RealTime, Se1),    /* watch the current time */
       write(">> The current time is "), write(RealTime), 
       Se2=do(watch_time(RealTime),Se1), 
   recover2(S1,Delta1,History1,Se2,Delta2,History2,S2).


recover1(S1,Delta1,History1,Se1,Delta2,History2,S2) :-
        nl, write(">> RECOVER1 is working..."), nl,
          sense(RealTime, Se1),    /* watch the current time */
          write(">> The current time is "), write(RealTime), 
          Se2=do(watch_time(RealTime),Se1), 
        History1 \== empty,
        History1 = trace(Delta, OldHistory), 
        ( S1= do(Action, S), 
          time(Action, ScheduledT),
          replaceTime(ScheduledT, RealTime, Delta, NewDelta), 
    /* Can we skip Action and the subsequent actions 
       and start anew ? */
          offline(NewDelta, Se2, Sg), nl,
          printf(">> Skip %w and subsequent actions\n", [Action]),
          Delta2 = NewDelta, History2= OldHistory, S2=Se2,
          current_stream(reports, X, Stream),
          printf(Stream, ">> Skip %w and subsequent actions\n", [Action]),
          printf(Stream, "\n >> Recovered program = %w\n 
                             >> New Situation = %w \n", [Delta2,S2]) ;
          recover1(S1,Delta1,OldHistory,Se2,Delta2,H2,S2) ).


recover2(S1,Delta1,History1,Se1,Delta2,History2,S2) :-
        nl, write(">> RECOVER2 is working..."), nl,
          sense(RealTime, Se1),    /* watch the current time */
          write(">> The current time is "), write(RealTime), 
          Se2=do(watch_time(RealTime),Se1), 
        History1 \== empty,
        History1 = trace(Delta, OldHistory), 
        ( S1= do(Action, S), 
          time(Action, ScheduledT),
          replaceTime(ScheduledT, RealTime, Delta, NewDelta),
          replaceTime(ScheduledT, RealTime, Action, NewAction),
  /* Can we do NewAction, skip the subsequent actions and start anew ? */       
          offline(NewAction : NewDelta, Se2, Sg), nl,
   printf(">> Do %w , but skip subsequent actions\n", [NewAction]),
          runAction(NewAction, Se2, S2),          
          Delta2 = NewDelta, History2= OldHistory,
          current_stream(reports, X, Stream),
          printf(Stream, ">> Skip %w and subsequent actions\n", [Action]),
          printf(Stream, "\n >> Recovered program = %w\n 
                             >> New Situation = %w \n", [Delta2,S2]) ;
          recover2(S1,Delta1,OldHistory,Se2,Delta2,H2,S2) ).


recover(S1,Delta1,History1,Se,Delta2,History2,S2) :-
	Delta2=fail, History2 = empty, S2=Se,
	nl,
	write(" Program cannot be recovered. "),
	write(" Monitor terminates its execution."), nl.

        
/* The following clause of "runAction" respects the schedule selected by
  the program:  ScheduledTime is the earliest time the action  A
  can start in the current situation Se under the condition that
  the remaining program Delta1 will lead to a successful termination.
  If the current time Time is less than ScheduledTime, wait until
  ScheduledTime, and then start executing.                      */

runAction(A,Se,S2) :- 
        time(A, ScheduledTime),  /* the time to start A */      
        start(Se, Time), 
             Time =< ScheduledTime,
        nl, write(" runAction is working"), nl,   
        PassTime is ScheduledTime - Time,
        ( PassTime > 0 -> myWait(PassTime,Se); true),        
        execute(A, ScheduledTime),    /* do action now in reality ! */
        S2 = do(A, Se),
        current_stream(reports, X, Stream),
        printf(Stream, "\n>> New situation = %w\n", [S2]),
        printf("\n >> New Situation = %w\n", [S2]).

/*
        util(V,S2), rmax(V), 
        printf("\n>> Situation = %w\n>> Utility = %w\n", [S2,V]),
        current_stream(reports, X, Stream),
        printf(Stream, "\n>> Situation = %w\n>> Utility = %w\n", [S2,V]).
*/

/* The following clause of "runAction" reschedules the action A
  if it is belated, but the delay is NOT relevant with respect
  to the execution of remaining program.
*/

runAction(A,Se,S2) :- 
        time(A, ScheduledT),       /* the time to start A */      
        start(Se, RealTime), 
            RealTime > ScheduledT,
        nl, write(" runAction is working"), nl,   
        replaceTime(ScheduledT,RealTime, A, Act),  /* reschedule action */
        execute(Act, RealTime),    /* do A now in reality ! */
        S2=do(Act, Se),
        current_stream(reports, X, Stream),
        printf(Stream, "\n>> New situation = %w\n", [S2]),
        printf("\n >> New Situation = %w\n", [S2]).

/*
        util(V,S2), rmax(V), 
        printf("\n>> Situation = %w\n>> Utility = %w\n", [S2,V]),
        current_stream(reports, X, Stream),
        printf(Stream, "\n>> Situation = %w\n>> Utility = %w\n", [S2,V]).
*/

	/* time sensing on robot  */
sense(Time, S):- 
            get_flag(unix_time, UnixTime),
            read(UnixStart) from_file scratch,
            Time is UnixTime - UnixStart.


	/* time sensing in simulation 
sense(Time, S):- 
            nl, write('>> Enter: current time.'), nl,
	 read(NewTime),
            start(S, OldTime),
            ( OldTime > NewTime -> sense(Time, S);
             Time = NewTime ).
*/

/*-----------------------------------------------------*
*                     Tools                             *
*------------------------------------------------------*/

setTime(A) :- time(A, Var), (nonground(Var) -> rmin(Var); true).


primitive_action(watch_time(RealTime)).
time(watch_time(RealTime), RealTime).

	/*  RUN  STUFF  */

coffee(S) :- online(deliverOneCoffee(3),empty, s0, S).
visit(S) :- online(serve,empty,s0,S).