3processSimpleFluent(Index, F=V, InitTime, QueryTime) :-
    4	isThereASimpleFPList(Index, F=V, ExtendedPList),
    5	setTheSceneSimpleFluent(ExtendedPList, F=V, InitTime, StPoint), 
    6	% compute the starting points within (Qi-WM,Qi] 
    7	computeStartingPoints(F=V, InitTime, QueryTime, InitList),
    8	% append the starting point of the interval, if any, starting
    9	% before or on Qi-WM and ending after Qi-WM   
   10	% to the starting points computed at this stage  
   11	addPoint(StPoint, InitList, CompleteInitList),
   12	% store the starting points of fluents that expire
   13	storeStartingPoints(Index, F=V, CompleteInitList),
   14	% compute new intervals
   15	holdsForSimpleFluent(F=V, NewIntervals, InitTime, QueryTime, CompleteInitList),
   16	% update simpleFPList
   17	computesimpleFPList(NewIntervals, InitTime, RestrictedPeriods, Extension),
   18	updatesimpleFPList(Index, F=V, RestrictedPeriods, Extension).
   19
   20
   21isThereASimpleFPList(Index, F=V, ExtendedPList) :-
   22	simpleFPList(Index, F=V, RestrictedList, Extension), !,
   23	retract(simpleFPList(Index, F=V, _, _)),
   24	amalgamatePeriods(Extension, RestrictedList, ExtendedPList).
   25
   26% this predicate deals with the case where no intervals for F=V were computed at the previous query time
   27isThereASimpleFPList(_Index, _U, []).
   28
   29
   30
   31/************************************************************************************************************* 
   32   This predicate is similar to setTheSceneSDFluent. The main difference is that instead of breaking
   33   the interval, if any, that starts before or on Qi-Memory and ends after Qi-Memory, we delete it (the 
   34   interval) and keep the starting point. cachedHoldsFor will create the fluent intervals given this 
   35   starting point and other starting and ending points within (Qi-WM,WM]. 
   36 *************************************************************************************************************/
   37
   38% deals with the case in which InitTime=<0
   39setTheSceneSimpleFluent(_EPList, F=V, InitTime, StPoint) :-
   40	InitTime=<0,
   41	( 
   42		initially(F=V), StPoint=[0] 
   43		;
   44		StPoint=[] 
   45	), !.
   46
   47% there is no need to update starting points in this case
   48% if there were any starting points then the first argument would not have been empty
   49setTheSceneSimpleFluent([], _U, _InitTime, []) :- !.
   50
   51% deals with the interval, if any, that starts before or on Qi-WM and ends after Qi-WM
   52setTheSceneSimpleFluent(EPList, _U, InitTime, StPoint) :-
   53	% look for an interval starting before or on Qi-WM and ending after Qi-WM
   54	InitTimePlus1 is InitTime+1,
   55	member((Start,End), EPList), 
   56	gt(End,InitTimePlus1),
   57	StartMinus1 is Start-1,
   58	(
   59		StartMinus1=<InitTime, StPoint=[Start]
   60		;
   61		StPoint=[]
   62	), !.    
   63
   64% all intervals end before Qi-WM 
   65setTheSceneSimpleFluent(_EPList, _U, _InitTime, []).
   66
   67
   68/****** compute starting points ******/
   69
   70computeStartingPoints(F=V, InitTime, QueryTime, InitList) :-
   71	initList(F=V, InitTime, QueryTime, InitList).
   72
   73% find the initiating time-points within (Qi-WM,Qi]
   74
   75initList(F=V, InitTime, QueryTime, InitList) :-
   76	EndTime is QueryTime+1,
   77	setof(T, initPoint(F=V, InitTime, EndTime, T), InitList), !.
   78
   79% if there is no initiating point
   80
   81initList(_, _, _, []).
   82 
   83
   84initPoint(F=V, InitTime, EndTime, NextTs) :-
   85	initiatedAt(F=V, InitTime, Ts, EndTime),
   86	nextTimePoint(Ts, NextTs).   
   87
   88
   89/****** compute ending points ******/
   90
   91computeEndingPoints(F=V, InitTime, QueryTime, TerminList) :-
   92	terminList(F=V, InitTime, QueryTime, TerminList).
   93
   94
   95% find the terminating time-points within (Qi-WM,Qi]
   96
   97terminList(F=V, InitTime, QueryTime, TerminList) :-
   98	EndTime is QueryTime+1,
   99	setof(T, termPoint(F=V, InitTime, EndTime, T), TerminList), !.
  100
  101% if there is no terminating point
  102
  103terminList(_, _, _, []).
  104
  105
  106termPoint(F=V, InitTime, EndTime, NextTs) :-
  107	broken(F=V, InitTime, Ts, EndTime),
  108	nextTimePoint(Ts, NextTs).
  109
  110
  111% 'Classic' Event Calculus
  112% BROKEN
  113
  114broken(U, Ts, Tf, T) :-
  115	terminatedAt(U, Ts, Tf, T).
  116
  117broken(F=V1, Ts, Tstar, T) :-  
  118    broken_v2(F=V1, Ts, Tstar, T).
  119
  120broken(F=V1, Ts, Tstar, T) :-
  121    rtec_v2, !,
  122    broken_v2(F=V1, Ts, Tstar, T).
  123
  124% master version and dsc-msc
  125broken(F=V1, Ts, Tstar, T) :-
  126	initiatedAt(F=V2, Ts, Tstar, T), 
  127	(strong_initiates ; V1 \= V2).   
  128  
  129% SimplEC version and V2 version
  130broken_v2(F=V1, Ts, Tstar, T) :-
  131	simpleFluent(F=V2), \+V2=V1,
  132	initiatedAt(F=V2, Ts, Tstar, T). 
  133	%(strong_initiates ; V1 \= V2).   
  134
  135% strong_initiates.
  136strong_initiates :- fail.    
  139/****** auxiliary predicate ******/
  140
  141addPoint([], L, L) :- !.
  142addPoint([P], L, [P|L]).
  143
  144/****** store the starting points of maxDurationUE fluents ******/
  145
  146storeStartingPoints(_, _, []) :- !.
  147storeStartingPoints(Index, F=V, SPoints) :-
  148	maxDurationUE(F=V, _, _),
  149	retract(startingPoints(Index, F=V, _)), !,
  150	assert(startingPoints(Index, F=V, SPoints)).
  151storeStartingPoints(Index, F=V, SPoints) :-
  152	maxDurationUE(F=V, _, _), !,
  153	assert(startingPoints(Index, F=V, SPoints)).
  154storeStartingPoints(Index, F=V, SPoints) :-
  155	cyclic(F=V),
  156	retract(startingPoints(Index, F=V, _)), !,
  157	assert(startingPoints(Index, F=V, SPoints)).
  158storeStartingPoints(Index, F=V, SPoints) :-
  159	cyclic(F=V), !,
  160	assert(startingPoints(Index, F=V, SPoints)).
  161storeStartingPoints(_, _, _).
  162
  163
  164
  165/****** compute new intervals given the computed starting and ending points ******/
  166
  167holdsForSimpleFluent(_U, [], _InitTime, _QueryTime, []) :- !.
  168
  169holdsForSimpleFluent(U, PeriodList, InitTime, QueryTime, InitList) :-
  170	% compute the ending points within (Qi-WM,Qi]
  171	computeEndingPoints(U, InitTime, QueryTime, TerminList),
  172	makeIntervalsFromSEPoints(InitList, TerminList, PeriodList).
  173      
  174
  175% makeIntervalsFromSEPoints(+ListofStartingPoints, +ListofEndingPoints, -MaximalIntervals) 
  176
  177makeIntervalsFromSEPoints(ListofStartingPoints, ListofEndingPoints, MaximalIntervals):- 
  178  rtec_v2, !, makeIntervalsFromSEPoints_v2(ListofStartingPoints, ListofEndingPoints, MaximalIntervals).
  179
  180makeIntervalsFromSEPoints(ListofStartingPoints, ListofEndingPoints, MaximalIntervals):- 
  181  makeIntervalsFromSEPoints_v1(ListofStartingPoints, ListofEndingPoints, MaximalIntervals).
  182
  183% the predicate below works under the assumption that the lists of 
  184% initiating and terminating points are temporally sorted
  185
  186
  187% master version and dsc-msc
  188% base cases: single initiation point
  189makeIntervalsFromSEPoints_v1([Ts], EPoints, Period) :-
  190	member(Tf, EPoints), 
  191	Ts=<Tf, 
  192	(
  193		Ts=Tf, !, 
  194		Period=[]
  195		;	
  196		%Ts<Tf
  197		!, Period=[(Ts,Tf)]
  198	).
  199makeIntervalsFromSEPoints_v1([Ts], _EPoints, [(Ts,inf)]) :- !.   
  200
  201% recursion: at least two initiation points
  202makeIntervalsFromSEPoints([T|MoreTs], [T|MoreTf], Periods) :-
  203	!, makeIntervalsFromSEPoints(MoreTs, MoreTf, Periods).
  204
  205makeIntervalsFromSEPoints_v1([Ts|MoreTs], [Tf|MoreTf], Periods) :-
  206	Tf<Ts, !, 
  207	makeIntervalsFromSEPoints([Ts|MoreTs], MoreTf, Periods).
  208
  209makeIntervalsFromSEPoints_v1([Ts,T|MoreTs], [T|MoreTf], [(Ts,T)|MorePeriods]) :-
  210	%Ts<Tf,  
  211	%Tf=Tnext, 
  212	!, makeIntervalsFromSEPoints([T|MoreTs], [T|MoreTf], MorePeriods).
  213
  214makeIntervalsFromSEPoints_v1([Ts,Tnext|MoreTs], [Tf|MoreTf], [(Ts,Tf)|MorePeriods]) :-
  215	%Ts<Tf,  
  216	Tf<Tnext, !,
  217	makeIntervalsFromSEPoints([Tnext|MoreTs], MoreTf, MorePeriods).
  218
  219makeIntervalsFromSEPoints_v1([Ts,Tnext|MoreTs], [Tf|MoreTf], [(Ts,Tf)|MorePeriods]) :-
  220	%Ts<Tnext<Tf,  
  221	!, makeIntervalsFromSEPoints([Tnext|MoreTs], [Tf|MoreTf], [(Tnext,Tf)|MorePeriods]).
  222
  223makeIntervalsFromSEPoints_v1([Ts,_Tnext|_MoreTs], _EPoints, [(Ts,inf)]).
  224
  225
  226% SimplEC version and V2 version
  227makeIntervalsFromSEPoints_v2([Ts], EPoints, [Period]) :-
  228	member(Tf, EPoints), 
  229	Ts<Tf, !,  
  230	Period = (Ts,Tf).
  231
  232makeIntervalsFromSEPoints_v2([Ts], _EPoints, [Period]) :- !,
  233	Period = (Ts,inf).    % simpler to deal with than since(Ts).
  234
  235makeIntervalsFromSEPoints_v2([Ts,Tnext|MoreTs], EPoints, [Period|MorePeriods]) :-
  236	member(Tf, EPoints), 
  237	Ts<Tf,
  238	(
  239		Tf<Tnext,
  240		Period=(Ts,Tf),
  241		append( _, [Tf|MoreEPoints], EPoints ), !,
  242		makeIntervalsFromSEPoints([Tnext|MoreTs], MoreEPoints, MorePeriods)
  243		;
  244		% U is neither initiated nor terminated between Ts and Tnext
  245		% need to amalgamate (Ts,Tnext) with next period found
  246		% Period=(Ts,Tf)
  247		% makeIntervalsFromSEPoints([Tnext|MoreTs], U, [(Tnext,Tf)|MorePeriods])	
  248		Period=(Ts,Tf), 
  249		MorePeriods=MoreX, 
  250        	append( _, [Tf|MoreEPoints], EPoints ), !,
  251		makeIntervalsFromSEPoints([Tnext|MoreTs], [Tf|MoreEPoints], [(Tnext,Tf)|MoreX])
  252	).
  253
  254makeIntervalsFromSEPoints_v2([Ts,_Tnext|_MoreTs], _EPoints, [(Ts,inf)]).
  255
  256/****** computesimpleFPList  ******/
  257
  258
  259computesimpleFPList([], _InitTime, [], []) :- !.
  260
  261computesimpleFPList([(Start,End)|Tail], InitTime, [(Start,End)|Tail], []) :-
  262	Start>InitTime, !.
  263
  264computesimpleFPList([(Start,End)|Tail], InitTime, [(NewInitTime,End)|Tail], [(Start,NewInitTime)]) :-
  265	nextTimePoint(InitTime, NewInitTime), 
  266	\+ NewInitTime = End, !.
  267
  268computesimpleFPList([Head|Tail], _InitTime, Tail, [Head]).
  269
  270
  271/****** updateSimpleFPList  ******/
  272
  273updatesimpleFPList(_Index, _U, [], []) :- !.
  274
  275updatesimpleFPList(Index, F=V, NewPeriods, BrokenPeriod) :- 
  276	assert(simpleFPList(Index, F=V, NewPeriods, BrokenPeriod))