I have been experimenting with the sCASP system – in particular trying to reproduce results from:
Joaquın Arias, Manuel Carro, Zhuo Chen, Gopal Gupta
Modeling and Reasoning in Event Calculus using Goal-Directed Constraint Answer Set Programming
(accessed from https://arxiv.org/pdf/2106.14566.pdf)
sCASP is extremely impressive and I look forward to applying it to real-world domains.
I have tried both the stable (9.0.4) and development (9.1.6) versions of SWI-Prolog and in both, using sCASP (version: 0.9.0), I get the same results.
For the simple light problem in figure 4 of the paper my code is:
/* bec_fig_04_light.pl
Steve Moyle 2023
Experiments with the Event Calculus using sCASP on SWI-Prolog version 9.0.4.
Attempting to reproduce results from:
Joaquın Arias, Manuel Carro, Zhuo Chen, Gopal Gupta
Modeling and Reasoning in Event Calculus using Goal-Directed Constraint Answer Set Programming
(accessed from https://arxiv.org/pdf/2106.14566.pdf)
*/
:- use_module(library(scasp)).
% BASIC EVENT CALCULUS (BEC) THEORY
:- discontiguous holdsAt/2.
:- discontiguous '-holdsAt'/2.
% BEC1 - StoppedIn(t1,f,t2)
stoppedIn(T1, Fluent, T2) :-
T1 #< T, T #< T2,
terminates(Event, Fluent, T),
happens(Event, T).
stoppedIn(T1, Fluent, T2) :-
T1 #< T, T #< T2,
releases(Event, Fluent, T),
happens(Event, T).
% BEC2 - StartedIn(t1,f,t2)
startedIn(T1, Fluent, T2) :-
T1 #< T, T #< T2,
initiates(Event, Fluent, T),
happens(Event, T).
startedIn(T1, Fluent, T2) :-
T1 #< T, T #< T2,
releases(Event, Fluent, T),
happens(Event, T).
% BEC3 - HoldsAt(f,t)
holdsAt(Fluent2, T2) :-
initiates(Event, Fluent1, T1),
happens(Event, T1),
trajectory(Fluent1, T1, Fluent2, T2),
not stoppedIn(T1, Fluent1, T2).
% BEC4 - HoldsAt(f,t)
holdsAt(Fluent, T) :-
0 #< T,
initiallyP(Fluent),
not stoppedIn(0, Fluent, T).
% BEC5 - not HoldsAt(f,t)
-holdsAt(Fluent, T) :-
0 #< T,
initiallyN(Fluent),
not startedIn(0, Fluent, T).
% BEC6 - HoldsAt(f,t)
holdsAt(Fluent, T2) :-
T1 #< T2,
initiates(Event, Fluent, T1),
happens(Event, T1),
not stoppedIn(T1, Fluent, T2).
% BEC7 - not HoldsAt(f,t)
-holdsAt(Fluent, T2) :-
T1 #< T2,
terminates(Event, Fluent, T1),
happens(Event, T1),
not startedIn(T1, Fluent, T2).
% End of BEC
% Encoding of Event Calculus narrative from Figure 4 from in paper (page 19)
% Actions
happens(turn_on, 2).
happens(turn_off, 4).
happens(turn_on, 5).
initiates(turn_on, on, _T).
terminates(turn_off, on, _T).
terminates(turn_off, red, _T).
terminates(turn_off, green, _T).
trajectory(on, T1, red, T2) :-
T2 #>= T1,
T2#<T1 + 1.
trajectory(on, T1, green, T2) :-
T2 #>= T1 + 1.
releases(turn_on, red, _T).
releases(turn_on, green, _T).
/* End of bec_fig_04_light.pl */
I get matching answers to the paper for:
?- ? holdsAt(on, 3).
Warning: scasp_predicate `'user:initiallyN'/1' does not exist
Warning: scasp_predicate `'user:initiallyP'/1' does not exist
:
But for
?- ? -holdsAt(on, 4.5).
Warning: scasp_predicate `'user:initiallyN'/1' does not exist
Warning: scasp_predicate `'user:initiallyP'/1' does not exist
ERROR: Type error: `rational' expected, found `4.5' (a float)
:
In the paper (page 23) the query should succeed. The paper has a footnote (7, page 23) that states that 4.5 is automatically converted to a rational so the constraint solver can deal with it.
?- ? holdsAt(F, 3).
:
Works as expected from the paper.
Note that a positive literal query with a float works as expected (NB: this is not from the paper).
? holdsAt(on, 4.5).
Warning: scasp_predicate `'user:initiallyN'/1' does not exist
Warning: scasp_predicate `'user:initiallyP'/1' does not exist
false.
The paper contains a second Event Calculus example using the same Basic Event Calculus (BEC) framework. In the following code I have removed the BEC from the top (it is the same as the first code above).
% Fig. 5: Encoding of an Event Calculus narrative with continuous change
:- discontiguous happens/2.
:- discontiguous initiates/3.
:- discontiguous terminates/3.
max_level(10) :- not max_level(16).
max_level(16) :- not max_level(10).
initiallyP(level(0)).
happens(overflow,_T).
happens(tapOn,5).
initiates(tapOn,filling,_T).
terminates(tapOff,filling,_T).
initiates(overflow,spilling,T):-
max_level(Max),
holdsAt(level(Max), T).
releases(tapOn,level(0),T):-
happens(tapOn,T).
trajectory(filling,T1,level(X2),T2):-
T1 #< T2,
X2 #= X + 4/3*(T2-T1),
max_level(Max),
X2 #=< Max,
holdsAt(level(X),T1).
trajectory(filling,T1,overlimit,T2):-
T1 #< T2,
X2 #= X + 4/3*(T2-T1),
max_level(Max),
X2 #> Max,
holdsAt(level(X),T1).
trajectory(spilling,T1,leak(X),T2):-
holdsAt(filling, T2),
T1 #< T2,
X #= 4/3*(T2-T1).
Replicating queries from section 4.1 Deduction (Page 23 of the paper)
?- ? holdsAt(level(H),15/2).
Warning: scasp_predicate `'user:initiallyN'/1' does not exist
H = 10r3,
Works as expected, whilst the following does not.
?- ? holdsAt(level(10/3),T).
Warning: scasp_predicate `'user:initiallyN'/1' does not exist
ERROR: Type error: `rational' expected, found `10/3' (a compound)
:
In the paper (page 23), T=15/2
.
Question: What is it about floats/rationals and or positive or negative queries that is causing my issues?
Overall, I remain super impressed with sCASP and am excited about its development.
Best wishes,
Steve
PS: I can provide stack traces if this cannot be easily reproduced.