Differnces between ciao s(casp) and swi s(Casp)

If I have the following program in swi:
SWISH -- SWI-Prolog for SHaring or

:- use_module(library(scasp)).
% Uncomment to suppress warnings
:- style_check(-discontiguous).
:- style_check(-singleton).
:- set_prolog_flag(scasp_unknown, fail).

#abducible causal_world(world1,smoking_causes_cancer).
#abducible causal_world(world2,cancer_causes_smoking).

false :- 
   causal_world(_,smoking_causes_cancer), 
   causal_world(_,cancer_causes_smoking).

precedes(X, Y) :- time(X, T1), time(Y, T2), T1 < T2.

temporal_constraint(World) :-
    causal_world(WorldN,smoking_causes_cancer),
    World = smoking_causes_cancer,
    precedes(smoking, cancer).

temporal_constraint(World) :-
    causal_world(WorldN,cancer_causes_smoking),
    World = cancer_causes_smoking,
    precedes(cancer, smoking).

% If we observe a violation of temporal constraints, that world becomes impossible
false :- 
   causal_world(WorldN,World),
   not temporal_constraint(World).

time(smoking, 2010).
time(cancer, 2015).

And I query:

? causal_world(W,Causes).

I get two answers for world1 and world2, which is not what I expect.

In ciao

https://ciao-lang.org/playground/scasp.html?code=%25%20Write%20your%20sCASP%20code%20here%2C%20e.g.%3A %23abducible%20causal_world(world1%2Csmoking_causes_cancer). %23abducible%20causal_world(world2%2Ccancer_causes_smoking). %3A-%20causal_world(_%2Csmoking_causes_cancer)%2C%20causal_world(_%2Ccancer_causes_smoking). precedes(X%2C%20Y)%20%3A-%20time(X%2C%20T1)%2C%20time(Y%2C%20T2)%2C%20T1%20<%20T2. temporal_constraint(World)%20%3A- %20%20%20%20causal_world(WorldN%2Csmoking_causes_cancer)%2C %20%20%20%20World%20%3D%20smoking_causes_cancer%2C %20%20%20%20precedes(smoking%2C%20cancer). temporal_constraint(World)%20%3A- %20%20%20%20causal_world(WorldN%2Ccancer_causes_smoking)%2C %20%20%20%20World%20%3D%20cancer_causes_smoking%2C %20%20%20%20precedes(cancer%2C%20smoking). %25%20If%20we%20observe%20a%20violation%20of%20temporal%20constraints%2C%20that%20world%20becomes%20impossible %3A-%20causal_world(WorldN%2CWorld)%2C%20not%20temporal_constraint(World). time(smoking%2C%202010). time(cancer%2C%202015). %25%20Example%20query%3A%20%3F-%20bob_goes. &ext=.pl


#abducible causal_world(world1,smoking_causes_cancer).
#abducible causal_world(world2,cancer_causes_smoking).

:- causal_world(_,smoking_causes_cancer), causal_world(_,cancer_causes_smoking).

precedes(X, Y) :- time(X, T1), time(Y, T2), T1 < T2.

temporal_constraint(World) :-
    causal_world(WorldN,smoking_causes_cancer),
    World = smoking_causes_cancer,
    precedes(smoking, cancer).

temporal_constraint(World) :-
    causal_world(WorldN,cancer_causes_smoking),
    World = cancer_causes_smoking,
    precedes(cancer, smoking).

% If we observe a violation of temporal constraints, that world becomes impossible
:- causal_world(WorldN,World), not temporal_constraint(World).

time(smoking, 2010).
time(cancer, 2015).

Query:

?- causal_world(W,Causes).

{ causal_world(world1,smoking_causes_cancer),  not causal_world(Var2 | {Var2 \= world1,Var2 \= world2},smoking_causes_cancer),  not causal_world(Var3 | {Var3 \= world1,Var3 \= world2},cancer_causes_smoking),  not causal_world(world1,cancer_causes_smoking),  not causal_world(world2,cancer_causes_smoking),  not causal_world(world2,smoking_causes_cancer),  not causal_world(Var4 | {Var4 \= world1,Var4 \= world2},Var5),  not causal_world(world1,Var6 | {Var6 \= smoking_causes_cancer}),  temporal_constraint(smoking_causes_cancer),  precedes(smoking,cancer),  time(smoking,2010),  time(cancer,2015),  not causal_world(world2,Var7 | {Var7 \= cancer_causes_smoking}) } 
W equal world1 
Causes equal smoking_causes_cancer ? ;

no

I seem to remember reading about some differnces in the swi implementation, but not sure if that is the case or I have made an error or if there is an option to get them to work the same?

In swi, I can get what I expect by querying:

? causal_world(W,Causes), temporal_constraint(Causes).

But I dont want to have to query with each constraint I might add?

There were fully equivalent at some point, but deviated a little after. I think Ciao sCASP switched the default forall algorithm. That is the thing that finds possible values for unbound variables. When ported, this used all. I recall @Xuaco switching this back to prev. I don’t recall the details. But, indeed using

?- set_prolog_flag(scasp_forall, prev).

We get one answer as you expected.

Thanks Jan!