2% ========================
    3/*
    4EVENT RECOGNITION LOOP
    5
    6--- initialiseRecognition(+InputFlag, +PreProcessingFlag, +TemporalDistance). 
    7InputFlag=ordered means that input facts are temporally sorted. 
    8InputFlag=any_other_value means that input facts are not temporally sorted. 
    9PreProcessingFlag=preprocessing means that there is a need for preprocessing by means of an application-dependent preProcessing/1. See the experiments on the CAVIAR dataset for an example of preprocessing.
   10PreProcessingFlag=any_other_value means that there is no need for preprocessing.
   11TemporalDistance is an integer denoting the distance between two consecutive time-points. Eg, in CAVIAR the temporal distance is 40.  
   12
   13Assert input facts at your leisure, even in a non-chronological manner. Then perform event recognition:
   14--- eventRecognition(+Qi, +WM).
   15where Qi is the current query time, and WM is the 'working memory'.
   16
   17A NOTE ON THE LISTS THAT ARE USED IN THE CODE
   18
   19-simpleFPList/sdFPList(Index, F=V, RestrictedList, Extension) where RestrictedList is the list of periods of the simple (statically determined) fluent within (Qi-WM, Qi] and Extension is the period before Qi-WM. Extension must be amalgamated with RestrictedList in order to produce the correct result of event recognition at Qi. F=V is an output entity.
   20-iePList(Index, F=V, RestrictedList, Extension) like above, except that F=V is an input entity.
   21-evTList: the time-points of output entity/event within (Qi-WM, Qi].
   22
   23---RTEC PREDICATES---
   24
   25The predicates below are available to the user:
   26
   27-happensAt(E, T) represents the time-points T in which an event E occurs.
   28-happensAt(start(F=V), T) represents a special event which takes place at the starting points of the maximal intervals of F=V. Similarly for happensAt(end(F=V), T). 
   29-initially(F=V) expresses that F=V at time 0.
   30-initiatedAt(F=V, _, T, _) states that at time T a period of time for which F=V is initiated. 
   31-terminatedAt(F=V, _, T, _) states that at time T a period of time for which F=V is terminated. 
   32-holdsFor(F=V, L) represents that the list of maximal intervals L during which F=V holds continuously.
   33-holdsAt(F=V, T) states that F=V holds at time-point T. 
   34
   35The predicates above are compiled into the following:
   36
   37-happensAtIE(E, T) represents the time-points T in which an input entity/event E occurs.
   38-happensAtProcessedIE(start(U), T) represents the time-points in which a special event 'start' occurs. The special event takes place at the starting points of the input entity/statically determined fluent U. The intervals of U are cached.  Similarly for happensAtProcessedIE(end(U), T).
   39-happensAtProcessedSimpleFluent(start(U), T) represents the time-points in which a special event 'start' occurs. The special event takes place at the starting points of the simple fluent U. The intervals of U are cached. Similarly for happensAtProcessedSimpleFluent(end(U), T).
   40-happensAtProcessedSDFluent(start(U), T) represents the time-points in which a special event 'start' occurs. The special event takes place at the starting points of the output entity/statically determined fluent U. The intervals of U are cached. Similarly for happensAtProcessedSDFluent(end(U), T).
   41-happensAtProcessed(E, T) represents the cached time-points T in which an output entity/event E occurs. E is not a start() or end() event.
   42-happensAtEv(E, T) represents the definition of an output entity/event.
   43-happensAt(E, T) is used for user interaction.
   44
   45-holdsForIESI(U, I) represents an interval I in which an input entity/statically determined fluent U occurs. Note that the second argument of this predicate is a single interval, as opposed to a list of intervals; underlying sensor data processing systems report single intervals as opposed to lists of intervals.
   46-holdsForProcessedIE(Index, IE, L) retrieves the cached list of intervals of an input entity/statically determined fluent.
   47-holdsForProcessedSimpleFluent(Index, F=V, L) retrieves the cached list of intervals of a simple fluent.
   48-holdsForProcessedSDFluent(Index, F=V, L) retrieves the cached list of intervals of an output entity/statically determined fluent.
   49-holdsForSDFluent(F=V, L) represents the definition of a durative output entity/statically determined fluent.
   50-holdsFor(F=V, L) is used for user interaction.
   51
   52-holdsAtProcessedIE(Index, F=V, T) checks whether a processed input entity/statically determined fluent holds at a given time-point.
   53-holdsAtProcessedSDFluent(Index, F=V, T) checks whether a cached output entity/statically determined fluent holds at a given time-point.
   54-holdsAtProcessedSimpleFluent(Index, F=V, T) checks whether a cached simple fluent holds at a given time-point.
   55-holdsAtSDFluent(Index, F=V, T) checks whether a statically determined fluent holds at a given time-point. This predicate is used when the intervals F=V are not cached.
   56-holdsAt(F=V, T) is used for user interaction.
   57
   58NOTE: statically determined fluents are defined only in terms of interval manipulation constructs, ie they are not defined by means of holdsAt.
   59NOTE: The second argument in holdsAtX query should be ground.
   60
   61DECLARATIONS:
   62
   63-event(E) states that E is an event.
   64-simpleFluent(F=V) states that F=V is a simple fluent.
   65-sDFluent(F=V) states that F=V is a statically determined fluent.
   66
   67-inputEntity(U) represents the input entities (events and/or statically determined fluents).
   68-outputEntity(U) represents the composite entities (events, simple fluents and/or statically determined fluents).
   69
   70-collectIntervals(F=V) states that the list of intervals of input entity/statically determined fluent F=V will be produced by the RTEC input module by collecting the reported individual intervals
   71-buildIntervals(F=V) states that the list of intervals of input entity/statically determined fluent F=V will be produced by the RTEC input module by gathering the reported time-points
   72 
   73-temporalDistance(TD) denotes the temporal distance between consecutive time-points. In some applications, such as video surveillance, there is a fixed temporal distance between time-points (video frames). In other applications this is not the case and therefore temporalDistance/1 should be undefined.
   74
   75-cachingOrder(Index, U) denotes the order of entity (event or fluent) processing. The first argument is the index of the entity.
   76*/
   77
   78% ========================
   79
   80:- set_prolog_flag(toplevel_print_options, [max_depth(100000)]).   81:- use_module(library(lists)).   82
   83:- ['compiler.prolog'].   84:- ['inputModule.prolog'].   85:- ['processSimpleFluents.prolog'].   86:- ['processSDFluents.prolog'].   87:- ['processEvents.prolog'].   88:- ['utilities/interval-manipulation.prolog'].   89:- ['utilities/amalgamate-periods.prolog'].   90
   91:- dynamic temporalDistance/1, input/1, preProcessing/1, initTime/1, iePList/4, simpleFPList/4, sdFPList/4, evTList/3, happensAtIE/2, holdsForIESI/2, 
   92   holdsAtIE/2, 
   93   processedCyclic/2, initiallyCyclic/1, storedCyclicPoints/3, startingPoints/3.   94
   95
   96/********************************** INITIALISE RECOGNITION ***********************************/
   97
   98
   99initialiseRecognition(InputFlag, PreProcessingFlag, TemporalDistance) :-
  100	assert(temporalDistance(TemporalDistance)),
  101	(InputFlag=ordered, assert(input(InputFlag)) ; assert(input(unordered))),
  102	% if we need preprocessing then preProcessing/1 is already defined
  103	% so there is no need to assert anything here
  104	(PreProcessingFlag=preprocessing ; assert(preProcessing(_))), !.
  105
  106
  107/************************************* EVENT RECOGNITION *************************************/
  108
  109rtec_v2 :- true.
  110
  111eventRecognition(QueryTime, WM) :-
  112    rtec_v2, 
  113    !, 
  114    eventRecognition_v2(QueryTime, WM).
  115eventRecognition(QueryTime, WM) :-
  116	InitTime is QueryTime-WM,
  117	assert(initTime(InitTime)),
  118        % delete input entities that have taken place before or on Qi-WM
  119	forget(InitTime),
  120	% compute the intervals of input entities/statically determined fluents
  121	inputProcessing(InitTime, QueryTime),
  122	preProcessing(QueryTime),
  123	% the order in which entities are processed makes a difference
  124	% start from lower-level entities and then move to higher-level entities
  125	% in this way the higher-level entities will use the CACHED lower-level entities
  126	% the order in which we process entities is set by cachingOrder/1 
  127	% which is specified in the domain-dependent file 
  128	% cachingOrder2/2 is produced in the compilation stage 
  129	% by combining cachingOrder/1, indexOf/2 and grounding/1
  130	findall(OE, (cachingOrder2(Index,OE), processEntity(Index,OE,InitTime,QueryTime)), _),
  131	retract(initTime(InitTime)).
  132
  133
  134eventRecognition_v2(QueryTime, WM) :-
  135	InitTime is QueryTime-WM,
  136	assert(initTime(InitTime)),
  137        % delete input entities that have taken place before or on Qi-WM
  138	forget(InitTime),
  139	% compute the intervals of input entities/statically determined fluents
  140	inputProcessing(InitTime, QueryTime),
  141	preProcessing(QueryTime),
  142	% CYCLES #1 CHANGE
  143	prepareCyclic,
  144	% CYCLES & DEADLINES CHANGE
  145	findall((Index,F=V,SPoints), (startingPoints(Index,F=V,SPoints),retract(startingPoints(Index,F=V,SPoints))), _),
  146	% DEADLINES #1 CHANGE
  147	findall((F=V,Duration), (maxDuration(F=V,_,Duration), deadlines1(F=V,Duration,InitTime)), _),
  148	% the order in which entities are processed makes a difference
  149	% start from lower-level entities and then move to higher-level entities
  150	% in this way the higher-level entities will use the CACHED lower-level entities
  151	% the order in which we process entities is set by cachingOrder/1 
  152	% which is specified in the domain-dependent file 
  153	% cachingOrder2/2 is produced in the compilation stage 
  154	% by combining cachingOrder/1, indexOf/2 and grounding/1
  155	findall(OE, (cachingOrder2(Index,OE), processEntity(Index,OE,InitTime,QueryTime)), _),
  156	% DEADLINES #2 CHANGE
  157	findall((F=V,Duration), (maxDuration(F=V,_,Duration), deadlines2(F=V,Duration,InitTime)), _),
  158	retract(initTime(InitTime)).
  159
  160processEntity(Index, OE, InitTime, QueryTime) :-
  161   rtec_v2, !, 
  162   processEntity_v2(Index, OE, InitTime, QueryTime).
  163
  164processEntity(Index, OE, InitTime, QueryTime) :-
  165	(
  166		% compute the intervals of output entities/statically determined fluents
  167		sDFluent(OE), 
  168		processSDFluent(Index, OE, InitTime) 
  169		;
  170		% compute the intervals of simple fluents 
  171		% (simple fluents are by definition output entities) 
  172		simpleFluent(OE), 
  173		processSimpleFluent(Index, OE, InitTime, QueryTime)
  174		;
  175		% compute the time-points of output entities/events
  176		processEvent(Index, OE)
  177	), !.
  178
  179
  180processEntity_v2(Index, OE, InitTime, QueryTime) :-
  181	(
  182		% compute the intervals of output entities/statically determined fluents
  183		sDFluent(OE), 
  184		processSDFluent(Index, OE, InitTime) 
  185		;
  186		% compute the intervals of simple fluents 
  187		% (simple fluents are by definition output entities) 
  188		simpleFluent(OE), 
  189		processSimpleFluent(Index, OE, InitTime, QueryTime),
  190		% CYCLES #2 CHANGE (no need to assert if not cyclic)
  191		assertCyclic(Index, OE)
  192		;
  193		% compute the time-points of output entities/events
  194		processEvent(Index, OE)
  195	), !.
  196
  197
  198/******************* deadlines treatment *********************/
  199
  200% Process deadline attempts computed at the previous query time
  201
  202% the rule below deals with fluents whose expiration may be extended
  203% ie maxDurationUE
  204% keep the happensAt(attempt(F=V),T) computed at the previous query time
  205% iff (a) holdsAt(F=V,nextTimePoint(Qi-WM)), (b) T>Qi-WM, and (c) T-Duration=<Qi-WM
  206deadlines1(F=V, Duration, InitTime) :-
  207	maxDurationUE(F=V, _, Duration), !,
  208	indexOf(Index, F=V), 
  209	retract( evTList(Index, attempt(F=V), ListofDeadlineAttempts) ),
  210	% (a) holdsAt(F=V,nextTimePoint(Qi-WM))
  211	simpleFPList(Index, F=V, I1, I2),
  212	amalgamatePeriods(I2, I1, I),
  213	nextTimePoint(InitTime, NextInitTime),
  214	tinIntervals(NextInitTime, I),
  215	% find the deadline attempt that satisfies conditions (b) and (c) mentioned above
  216	% this predicate is defined below
  217	findDeadlineAttempt(ListofDeadlineAttempts, Attempt, InitTime, Duration), 
  218	assert( evTList(Index, attempt(F=V), Attempt) ).
  219	
  220% === find the deadline attempt that satisfies conditions (b) and (c) mentioned above	 ===
  221findDeadlineAttempt([], [], _, _) :- !.	
  222
  223findDeadlineAttempt([Attempt], [Attempt], InitTime, Duration) :-
  224	% (b) the deadline attempt time is after Qi-WM
  225	Attempt>InitTime,
  226	% (c) the initiating conditions of the deadline attempt
  227	% are before or on Qi-WM	
  228	EarlyT is Attempt-Duration, EarlyT=<InitTime, !.
  229
  230findDeadlineAttempt([_], [], _, _) :- !.	
  231	
  232findDeadlineAttempt([A1,A2|Tail], [A1], InitTime, Duration) :-
  233	% (b) the deadline attempt time is after Qi-WM
  234	A1>InitTime,
  235	% (c) the initiating conditions of the deadline attempt
  236	% are before or on Qi-WM	
  237	EarlyT1 is A1-Duration, EarlyT1=<InitTime,
  238	EarlyT2 is A2-Duration, EarlyT2>InitTime, !.
  239	
  240findDeadlineAttempt([A1,A2|Tail], Attempt, InitTime, Duration) :-
  241	findDeadlineAttempt([A2|Tail], Attempt, InitTime, Duration).
  242% === find the deadline attempt that satisfies conditions (b) and (c) mentioned above	 ===
  243
  244
  245% the rule below deals with fluents whose expiration may NOT be extended
  246% keep the happensAt(attempt(F=V),T) computed at the previous query time
  247% iff (a) holdsAt(F=V,nextTimePoint(Qi-WM)), (b) T>Qi-WM, (c) T-Duration=<Qi-WM and
  248% (d) T-Duration=S where S is the start of the interval starting 
  249% before or on Qi-WM and ending after for which F=V 
  250deadlines1(F=V, Duration, InitTime) :-
  251	indexOf(Index, F=V),
  252	retract( evTList(Index, attempt(F=V), ListofDeadlineAttempts) ),	
  253	% (a) holdsAt(F=V,nextTimePoint(Qi-WM))
  254	simpleFPList(Index, F=V, I1, I2),
  255	amalgamatePeriods(I2, I1, I),
  256	nextTimePoint(InitTime, NextInitTime),
  257	% we do not use tinIntervals as above because we also want S  
  258	member((S,E),I), gt(E,NextInitTime), !, S=<NextInitTime,
  259	member(Attempt, ListofDeadlineAttempts),
  260	% (b) the deadline attempt time is after Qi-WM
  261	Attempt>InitTime,
  262	EarlyT is Attempt-Duration, 
  263	% (c) the initiating conditions of the deadline attempt
  264	% are before or on Qi-WM	
  265	EarlyT=<InitTime,
  266	% (d) Attempt-Duration=S where S is the start of the interval  
  267	% starting before or on Qi-WM and ending after for which F=V 
  268	prevTimePoint(S,PrevS), EarlyT=PrevS, 
  269	% ListofDeadlineAttempts is sorted
  270	!,
  271	assert( evTList(Index, attempt(F=V), [Attempt]) ).
  272
  273% deadlines2/1 computes and stores the deadline attempts
  274
  275% the two rules below deal with fluents whose expiration may be extended
  276
  277% the rule below deals with the case where there are
  278% dealine attempts from the previous query time
  279deadlines2(F=V, Duration, InitTime) :-
  280	maxDurationUE(F=V, _, Duration),
  281	indexOf(Index, F=V),
  282	retract( evTList(Index, attempt(F=V), List) ), !,
  283	startingPoints(Index, F=V, SPoints),
  284	findall(T, 
  285		(member(S,SPoints), prevTimePoint(S,PrevS), PrevS>InitTime, T is PrevS+Duration), 
  286	NewList),
  287	append(List, NewList, AppendedList),
  288	% the predicate below is defined in processEvents.prolog
  289	updateevTList(Index, attempt(F=V), AppendedList).
  290% the rule below deals with the case where there are NO
  291% dealine attempts from the previous query time
  292deadlines2(F=V, Duration, InitTime) :-
  293	maxDurationUE(F=V, _, Duration), !,
  294	indexOf(Index, F=V),
  295	startingPoints(Index, F=V, SPoints),
  296	findall(T, 
  297		(member(S,SPoints), prevTimePoint(S,PrevS), PrevS>InitTime, T is PrevS+Duration), 
  298	NewList),
  299	% the predicate below is defined in processEvents.prolog
  300	updateevTList(Index, attempt(F=V), NewList).
  301
  302% the two rules below deal with fluents whose expiration may NOT be extended
  303
  304% the rule below deals with the case where there are
  305% dealine attempts from the previous query time
  306deadlines2(F=V, Duration, InitTime) :-
  307	indexOf(Index, F=V),
  308	retract( evTList(Index, attempt(F=V), List) ), !,
  309	simpleFPList(Index, F=V, I1, I2),
  310	amalgamatePeriods(I2, I1, I),
  311	findall(T, 
  312		(member((S,_),I), prevTimePoint(S,PrevS), PrevS>InitTime, T is PrevS+Duration), 
  313	NewList),
  314	append(List, NewList, AppendedList),
  315	% the predicate below is defined in processEvents.prolog
  316	updateevTList(Index, attempt(F=V), AppendedList).
  317% the rule below deals with the case where there are NO
  318% dealine attempts from the previous query time
  319deadlines2(F=V, Duration, InitTime) :-
  320	indexOf(Index, F=V),
  321	simpleFPList(Index, F=V, I1, I2),
  322	amalgamatePeriods(I2, I1, I),
  323	findall(T, 
  324		(member((S,_),I), prevTimePoint(S,PrevS), PrevS>InitTime, T is PrevS+Duration), 
  325	NewList),
  326	% the predicate below is defined in processEvents.prolog
  327	updateevTList(Index, attempt(F=V), NewList).
  328
  329
  330/******************* cycles treatment *********************/
  331
  332prepareCyclic :-
  333	% check if there are cycles in the event description
  334	cyclic(_), !,
  335	findall((Index,F=V,L), (storedCyclicPoints(Index,F=V,L), retract(storedCyclicPoints(Index,F=V,L))), _),
  336	findall((Index,F=V), (processedCyclic(Index,F=V), retract(processedCyclic(Index,F=V))), _),
  337	findall(F=V, (initiallyCyclic(F=V), retract(initiallyCyclic(F=V))), _),
  338	assertInitiallyCyclic.
  339prepareCyclic.
  340
  341assertInitiallyCyclic :-
  342	initTime(InitTime),
  343	InitTime>0, !, 
  344	nextTimePoint(InitTime, NextInitTime),
  345	findall(F=V, 
  346	  (
  347	    cyclic(F=V),
  348	    indexOf(Index, F=V),
  349	    simpleFPList(Index, F=V, I1, I2),
  350	    amalgamatePeriods(I2, I1, I),
  351	    tinIntervals(NextInitTime, I),
  352	    assert(initiallyCyclic(F=V))), 
  353	  _).
  354assertInitiallyCyclic :-
  355	 % InitTime=<0
  356	 findall(F=V, 
  357	  (
  358	    cyclic(F=V),
  359	    grounding(F=V),
  360	    %initially(F=V),
  361	    initiatedAt(F=V, -1, -1, 0),
  362	    assert(initiallyCyclic(F=V))), 
  363	  _).
  364	  
  365assertCyclic(Index, F=V) :- 
  366	  cyclic(F=V), !,
  367	  assert(processedCyclic(Index, F=V)).
  368assertCyclic(_, _).
  369
  370% T is ground when evaluating holdsAt
  371% if the intervals of the cyclic fluent have been already computed then look no further
  372holdsAtCyclic(Index, F=V, T) :-
  373	processedCyclic(Index, F=V), !,
  374	holdsAtProcessedSimpleFluent(Index, F=V, T).
  375% check whether we already know whether holdsAt(F=V, T)
  376holdsAtCyclic(Index, F=V, T) :-
  377	% storedSFPoints stores some, but not necessarily all points of a cyclic fluent
  378	% therefore, the cut in this rule has to go the end 
  379	storedCyclicPoints(Index, F=V, StoredPoints), 
  380	lastPointBeforeOrOnT(T, StoredPoints, (Point,Val)), !, 
  381	findFluentVal(Index, F=V, T, (Point,Val)).
  382% the rule below are classic EC simple fluent computation
  383holdsAtCyclic(Index, F=V, T) :-
  384	initTime(InitTime), 
  385	initPointBetween(Index, F=V, InitTime, InitPoint, T),
  386	nextTimePoint(InitPoint, NextPoint),
  387	notBrokenOrReInitiated(Index, F=V, NextPoint, T), 
  388	% since we computed a time-point for the cyclic fluent we store it 
  389	% in order to avoid recomputing it in the future
  390	addCyclicPoint(Index, F=V, T, t), !.
  391% store that we failed to prove holdsAt(F=V, T)
  392holdsAtCyclic(Index, F=V, T) :-
  393	addCyclicPoint(Index, F=V, T, f), !, false.
  394	
  395	
  396lastPointBeforeOrOnT(T, [(X,Val)], (X,Val)) :- !, X=<T.	
  397lastPointBeforeOrOnT(T, [(X1,Val1),(X2,_)|_], (X1,Val1)) :- X1=<T, X2>T, !.	
  398lastPointBeforeOrOnT(T, [(X,_)|Rest0], R) :-
  399	X<T, lastPointBeforeOrOnT(T, Rest0, R).		
  400	
  401findFluentVal(_Index, _U, T, (T,Val)) :- !, Val=t.
  402findFluentVal(Index, F=V, T, (Point,t)) :-
  403	notBrokenOrReInitiated(Index, F=V, Point, T), !,
  404	addCyclicPoint(Index, F=V, T, t).
  405findFluentVal(Index, F=V, T, (_Point,t)) :-
  406	addCyclicPoint(Index, F=V, T, f), !, false.
  407findFluentVal(Index, F=V, T, (Point,f)) :-
  408	startedBetween(Index, F=V, Point, InitPoint, T),
  409	nextTimePoint(InitPoint, NextPoint),
  410	notBrokenOrReInitiated(Index, F=V, NextPoint, T), !,
  411	addCyclicPoint(Index, F=V, T, t).
  412findFluentVal(Index, F=V, T, (_Point,f)) :-
  413	addCyclicPoint(Index, F=V, T, f), !, false.
  414	
  415% we are looking in the interval [Ts,Te)
  416notBrokenOrReInitiated(_, _, Ts, Te) :- Ts>=Te, !.
  417notBrokenOrReInitiated(Index, F=V, Ts, Te) :-
  418	brokenOnce(Index, F=V, Ts, T, Te), !,	
  419	nextTimePoint(T, NextT),
  420	startedBetween(Index, F=V, NextT, Init, Te),
  421	notBrokenOrReInitiated(Index, F=V, Init, Te).
  422notBrokenOrReInitiated(_, _, _, _).	
  423
  424% we are looking in the interval [Ts,Te)
  425brokenOnce(Index, F=V1, Ts, T, Te) :-
  426	simpleFluent(F=V2), \+V2=V1,
  427	startedBetween(Index, F=V2, Ts, T, Te), !.
  428brokenOnce(_Index, F=V, Ts, T, Te) :-
  429	terminatedAt(F=V, Ts, T, Te), !.
  430
  431% we are looking in the interval [Ts,Te)
  432startedBetween(_, _, Ts, _, Te) :- Ts>=Te, !, false.
  433startedBetween(Index, F=V, Ts, T, Te) :-
  434	startingPoints(Index, F=V, SPoints),
  435	member(SPoint, SPoints), 
  436	prevTimePoint(SPoint, T), 
  437	Ts=<T, !, T<Te.	
  438startedBetween(Index, F=V, Ts, T, Te) :-
  439	initiatedAt(F=V, Ts, T, Te), !,
  440	addStartingPoint(Index, F=V, T).
  441
  442% we are looking in the interval [Ts,Te)
  443initPointBetween(Index, F=V, Ts, T, Te) :-
  444	startingPoints(Index, F=V, SPoints), 
  445	member(SPoint, SPoints), 
  446	prevTimePoint(SPoint, T), 
  447	Ts=<T, !, T<Te.	
  448initPointBetween(_Index, F=V, Ts, Ts, Te) :- 
  449	Ts<Te, initiallyCyclic(F=V), !.		
  450initPointBetween(Index, F=V, Ts, T, Te) :-
  451	nextTimePoint(Ts, NextTs),
  452	initiatedAt(F=V, NextTs, T, Te), !,
  453	addStartingPoint(Index, F=V, T).
  454
  455	
  456addStartingPoint(Index, F=V, InitPoint) :-
  457	retract(startingPoints(Index, F=V, SPoints)), !,
  458	nextTimePoint(InitPoint, SPoint),
  459	insertNo(SPoint, SPoints, NewSPoints),
  460	assert(startingPoints(Index, F=V, NewSPoints)).
  461addStartingPoint(Index, F=V, InitPoint) :-
  462	nextTimePoint(InitPoint, SPoint),
  463	assert(startingPoints(Index, F=V, [SPoint])).
  464	
  465addCyclicPoint(Index, F=V, T, Val) :-
  466	retract(storedCyclicPoints(Index, F=V, OldCPoints)), !, 
  467	insertTuple((T,Val), OldCPoints, NewCPoints),
  468	assert(storedCyclicPoints(Index, F=V, NewCPoints)).
  469addCyclicPoint(Index, F=V, T, Val) :-
  470	assert(storedCyclicPoints(Index, F=V, [(T,Val)])).	
  471
  472insertNo(X, [], [X]).
  473insertNo(X, [X|Rest], [X|Rest]) :- !.
  474insertNo(X, [Y|Rest], [X,Y|Rest]) :- X<Y, !.
  475insertNo(X, [Y|Rest0], [Y|Rest]) :- 
  476	insertNo(X, Rest0, Rest).		
  477	
  478insertTuple(X, [], [X]) :- !.
  479insertTuple((X,Val), [(X,Val)|Rest], [(X,Val)|Rest]) :- !.
  480insertTuple((X,Val), [(Y,Val2)|Rest], [(X,Val),(Y,Val2)|Rest]) :- X<Y, !.
  481insertTuple(X, [Y|Rest0], [Y|Rest]) :-
  482	insertTuple(X, Rest0, Rest).
  483
  484/******************* entity index: use of cut to avoid backtracking *********************/
  485
  486indexOf(Index, E) :-
  487	index(E, Index), !.
  488
  489/******************* APPLICATION-INDEPENDENT holdsFor, holdsAt AND happensAt (INCARNATIONS) *********************/
  490
  491
  492%%%%%%% holdsFor as used in the body of entity definitions
  493
  494% processed input entity/statically determined fluent
  495holdsForProcessedIE(Index, IE, L) :- 
  496  	iePList(Index, IE, L, _), !.
  497
  498holdsForProcessedIE(_Index, _IE, []).
  499
  500% cached simple fluent
  501holdsForProcessedSimpleFluent(Index, F=V, L) :-	
  502	simpleFPList(Index, F=V, L, _), !.
  503
  504holdsForProcessedSimpleFluent(_Index, _U, []).
  505
  506% cached output entity/statically determined fluent
  507holdsForProcessedSDFluent(Index, F=V, L) :- 
  508  	sdFPList(Index, F=V, L, _), !.
  509
  510holdsForProcessedSDFluent(_Index, _U, []).
  511
  512
  513%%%%%%% holdsAt as used in the body of entity definitions
  514
  515% T should be given in all 4 predicates below
  516
  517% processed input entity/statically determined fluent
  518holdsAtProcessedIE(Index, F=V, T) :- 
  519  	iePList(Index, F=V, [H|Tail], _),
  520	tinIntervals(T, [H|Tail]).
  521
  522% cached simple fluent
  523holdsAtProcessedSimpleFluent(Index, F=V, T) :-	
  524	simpleFPList(Index, F=V, [H|Tail], _),
  525	tinIntervals(T, [H|Tail]).
  526
  527% cached output entity/statically determined fluent
  528holdsAtProcessedSDFluent(Index, F=V, T) :- 
  529  	sdFPList(Index, F=V, [H|Tail], _),
  530	tinIntervals(T, [H|Tail]).
  531
  532% statically determined fluent that is neither an input entity nor an output entity
  533% ie the intervals of F=V are not cached
  534holdsAtSDFluent(F=V, T) :- 
  535  	holdsForSDFluent(F=V, [H|Tail]),
  536	tinIntervals(T, [H|Tail]).
  537
  538
  539%%%%%%% happensAt as used in the body of entity definitions
  540
  541%%%% special event: the starting time of a fluent
  542
  543%%% in each case below (input entity/statically determined fluent, simple fluent 
  544%%% and output entity/statically determined fluent), the first rule checks if 
  545%%% the first interval in (Qi-WM, Qi] is amalgamated with the last interval before Qi-WM
  546%%% If it is then start(F=V) does not take place at the starting time 
  547%%% of the first interval in (Qi-WM, Qi]
  548
  549
  550:- if(rtec_v2).  551
  552% old compute the starting points of processed input entities/statically determined fluents
  553happensAtProcessedIE(Index, start(F=V), T) :-
  554	iePList(Index, F=V, [(IntervalBreakingPoint,_)|Tail], [(_,IntervalBreakingPoint)]), 
  555	member((S,_E), Tail), prevTimePoint(S, T).
  556happensAtProcessedIE(Index, start(F=V), T) :-
  557	iePList(Index, F=V, [H|Tail], []), 
  558	member((S,_E), [H|Tail]), prevTimePoint(S, T).
  559% compute the starting points of simple fluents
  560happensAtProcessedSimpleFluent(Index, start(F=V), T) :-
  561	simpleFPList(Index, F=V, [(IntervalBreakingPoint,_)|Tail], [(_,IntervalBreakingPoint)]), 
  562	member((S,_E), Tail), prevTimePoint(S, T).
  563happensAtProcessedSimpleFluent(Index, start(F=V), T) :-
  564	simpleFPList(Index, F=V, [H|Tail], []),
  565	member((S,_E), [H|Tail]), prevTimePoint(S, T).
  566% compute the starting points of output entities/statically determined fluents
  567happensAtProcessedSDFluent(Index, start(F=V), T) :-
  568	sdFPList(Index, F=V, [(IntervalBreakingPoint,_)|Tail], [(_,IntervalBreakingPoint)]),  
  569	member((S,_E), Tail), prevTimePoint(S, T).
  570happensAtProcessedSDFluent(Index, start(F=V), T) :-
  571	sdFPList(Index, F=V, [H|Tail], []), 
  572	member((S,_E), [H|Tail]), prevTimePoint(S, T).
  573
  574% start(F=V) is not defined for fluents that are neither input nor output entities, 
  575% ie fluents that are not cached
  576% For such fluents we do not have access to the last interval before Qi-WM 
  577% and therefore we cannot compute whether the last interval before Qi-WM 
  578% is amalgamated with the first interval in (Qi-WM,Qi]
  579
  580
  581%%%% special event: the ending time of a fluent interval 
  582/*
  583% compute the ending points of processed input entities/statically determined fluents
  584happensAtProcessedIE(Index, end(F=V), E) :-
  585	iePList(Index, F=V, [H|Tail], _), 
  586	member((_S,E), [H|Tail]), \+ E=inf.
  587% compute the ending points of simple fluents
  588happensAtProcessedSimpleFluent(Index, end(F=V), E) :-
  589	simpleFPList(Index, F=V, [H|Tail], _),
  590	member((_S,E), [H|Tail]), \+ E=inf.
  591% compute the ending points of output entities/statically determined fluents
  592happensAtProcessedSDFluent(Index, endO(F=V), E) :-
  593	sdFPList(Index, F=V, [H|Tail], _), 
  594	member((_S,E), [H|Tail]), \+ E=inf.
  595% compute the ending points of statically determined fluents
  596% that are neither input nor output entities, ie these fluents are not cached
  597happensAtSDFluent(endO(F=V), E) :-
  598	holdsForSDFluent(F=V, [H|Tail]), 
  599	member((_S,E), [H|Tail]), \+ E=inf.
  600*/
  601% compute the ending points of processed input entities/statically determined fluents
  602happensAtProcessedIE(Index, end(F=V), T) :-
  603	iePList(Index, F=V, [H|Tail], _), 
  604	member((_S,E), [H|Tail]),
  605	\+ E=inf, prevTimePoint(E, T).
  606% compute the ending points of simple fluents
  607happensAtProcessedSimpleFluent(Index, end(F=V), T) :-
  608	simpleFPList(Index, F=V, [H|Tail], _),
  609	member((_S,E), [H|Tail]), 
  610	\+ E=inf, prevTimePoint(E, T).
  611% compute the ending points of output entities/statically determined fluents
  612happensAtProcessedSDFluent(Index, end(F=V), T) :-
  613	sdFPList(Index, F=V, [H|Tail], _), 
  614	member((_S,E), [H|Tail]),
  615	\+ E=inf, 
  616    prevTimePoint(E, T).
  617% compute the ending points of statically determined fluents
  618% that are neither input nor output entities, ie these fluents are not cached
  619happensAtSDFluent(end(F=V), T) :-
  620	holdsForSDFluent(F=V, [H|Tail]), 
  621	member((_S,E), [H|Tail]),
  622	\+ E=inf, prevTimePoint(E, T).
  623
  624:- else.  625% compute the starting points of processed input entities/statically determined fluents
  626happensAtProcessedIE(Index, start(F=V), S) :-
  627	iePList(Index, F=V, [(IntervalBreakingPoint,_)|Tail], [(_,IntervalBreakingPoint)]), !,
  628	member((S,_E), Tail).
  629
  630happensAtProcessedIE(Index, start(F=V), S) :-
  631	iePList(Index, F=V, [H|Tail], _), 
  632	member((S,_E), [H|Tail]).
  633
  634% compute the starting points of simple fluents
  635happensAtProcessedSimpleFluent(Index, start(F=V), S) :-
  636	simpleFPList(Index, F=V, [(IntervalBreakingPoint,_)|Tail], [(_,IntervalBreakingPoint)]), !,
  637	member((S,_E), Tail).
  638
  639happensAtProcessedSimpleFluent(Index, start(F=V), S) :-
  640	simpleFPList(Index, F=V, [H|Tail], _),
  641	member((S,_E), [H|Tail]).
  642
  643% compute the starting points of output entities/statically determined fluents
  644happensAtProcessedSDFluent(Index, start(F=V), S) :-
  645	sdFPList(Index, F=V, [(IntervalBreakingPoint,_)|Tail], [(_,IntervalBreakingPoint)]), !, 
  646	member((S,_E), Tail).
  647
  648happensAtProcessedSDFluent(Index, start(F=V), S) :-
  649	sdFPList(Index, F=V, [H|Tail], _), 
  650	member((S,_E), [H|Tail]).
  651	
  652% start(F=V) is not defined for fluents that are neither input nor output entities, 
  653% ie fluents that are not cached
  654% For such fluents we do not have access to the last interval before Qi-WM 
  655% and therefore we cannot compute whether the last interval before Qi-WM 
  656% is amalgamated with the first interval in (Qi-WM,Qi]
  657
  658
  659%%%% special event: the ending time of a fluent
  660
  661% compute the ending points of processed input entities/statically determined fluents
  662happensAtProcessedIE(Index, end(F=V), E) :-
  663	iePList(Index, F=V, [H|Tail], _), 
  664	member((_S,E), [H|Tail]),
  665	\+ E=inf.
  666
  667% compute the ending points of simple fluents
  668happensAtProcessedSimpleFluent(Index, end(F=V), E) :-
  669	simpleFPList(Index, F=V, [H|Tail], _),
  670	member((_S,E), [H|Tail]),
  671	\+ E=inf.
  672
  673% compute the ending points of output entities/statically determined fluents
  674happensAtProcessedSDFluent(Index, end(F=V), E) :-
  675	sdFPList(Index, F=V, [H|Tail], _), 
  676	member((_S,E), [H|Tail]),
  677	\+ E=inf.
  678	
  679% compute the ending points of statically determined fluents
  680% that are neither input nor output entities, ie these fluents are not cached
  681happensAtSDFluent(end(F=V), E) :-
  682	holdsForSDFluent(F=V, [H|Tail]), 
  683	member((_S,E), [H|Tail]),
  684	\+ E=inf.
  685
  686:- endif.  687
  688%%%% happensAtProcessed for non-special events
  689
  690% cached events
  691happensAtProcessed(Index, E, T) :-
  692	evTList(Index, E, L),
  693	member(T, L).
  694
  695
  696%%%%%%% USER INTERACTION %%%%%%%
  697
  698%%%%%%% holdsFor is used ONLY for user interaction
  699%%%%%%% use iePList/simpleFPList/sdFPList and look no further
  700
  701holdsFor(F=V, L) :-
  702	retrieveIntervals(F=V, L).
  703
  704% retrieve the intervals of input entities (those for which we collect their intervals)
  705retrieveIntervals(F=V, L) :-
  706	% collectIntervals2/2 is produced in the compilation stage 
  707	% by combining collectIntervals/1, indexOf/2 and grounding/1
  708	collectIntervals2(Index, F=V),
  709	retrieveIEIntervals(Index, F=V, L).
  710
  711% retrieve the intervals of input entities (those for which we build their intervals from time-points)
  712retrieveIntervals(F=V, L) :-
  713	% buildFromPoints2/2 is produced in the compilation stage 
  714	% by combining collectIntervals/1, indexOf/2 and grounding/1
  715	buildFromPoints2(Index, F=V),
  716	retrieveIEIntervals(Index, F=V, L).
  717
  718% retrieve the intervals of output entities
  719retrieveIntervals(F=V, L) :-
  720	% cachingOrder2/2 is produced in the compilation stage 
  721	% by combining cachingOrder/1, indexOf/2 and grounding/1
  722	cachingOrder2(Index, F=V),
  723	retrieveOEIntervals(Index, F=V, L).
  724
  725
  726retrieveIEIntervals(Index, F=V, L) :-
  727	iePList(Index, F=V, RestrictedList, Extension), !,
  728	amalgamatePeriods(Extension, RestrictedList, L).
  729
  730retrieveIEIntervals(_Index, _U, []).
  731
  732
  733retrieveOEIntervals(Index, F=V, L) :-
  734	sDFluent(F=V), !,
  735	retrieveOESDFluentIntervals(Index, F=V, L).
  736
  737retrieveOEIntervals(Index, F=V, L) :-
  738	simpleFPList(Index, F=V, RestrictedList, Extension), !,
  739	amalgamatePeriods(Extension, RestrictedList, L).
  740
  741retrieveOEIntervals(_Index, _U, []).
  742
  743
  744retrieveOESDFluentIntervals(Index, F=V, L) :-
  745	sdFPList(Index, F=V, RestrictedList, Extension), !,
  746	amalgamatePeriods(Extension, RestrictedList, L).
  747
  748retrieveOESDFluentIntervals(_Index, _U, []).
  749
  750
  751%%%%%%% holdsAt is used ONLY for user interaction
  752% T should be given
  753
  754holdsAt(F=V, T) :-
  755	holdsFor(F=V, [H|Tail]),
  756	tinIntervals(T, [H|Tail]).
  757
  758
  759tinIntervals(T, L) :-
  760	member((S,E), L),
  761	gt(E,T), !, S=<T.
  762
  763
  764%%%%%%% happensAt is used ONLY for user interaction
  765
  766% retrieve the time-points of input entities
  767happensAt(E, T) :-
  768	inputEntity(E),
  769	happensAtIE(E, T).
  770
  771% retrieve the time-points of output entities
  772happensAt(E, T) :-
  773	event(E), 
  774	% cachingOrder2/2 is produced in the compilation stage 
  775	% by combining cachingOrder/1, indexOf/2 and grounding/1
  776	cachingOrder2(Index, E),
  777	happensAtProcessed(Index, E, T)