I’m using s(CASP) through SwiplServer, and running the following code:
:- use_module(library(scasp)).
:- style_check(-discontiguous).
:- style_check(-singleton).
:- set_prolog_flag(scasp_unknown, fail).
#pred bird(X) :: '@(X) is a bird'.
#pred according_to(R,bird(X)) :: 'according to @(R), @(X) is a bird'.
#pred legally_holds(_,bird(X)) :: 'it legally holds that @(X) is a bird'.
#pred penguin(X) :: '@(X) is a penguin'.
#pred according_to(R,penguin(X)) :: 'according to @(R), @(X) is a penguin'.
#pred legally_holds(_,penguin(X)) :: 'it legally holds that @(X) is a penguin'.
bird(X) :-
penguin(X).
#pred thing(X) :: '@(X) is a thing'.
#pred according_to(R,thing(X)) :: 'according to @(R), @(X) is a thing'.
#pred legally_holds(_,thing(X)) :: 'it legally holds that @(X) is a thing'.
#pred flies(Y,X) :: 'it is @(X) that @(Y) flies'.
#pred according_to(R,flies(Y,X)) :: 'according to @(R), it is @(X) that @(Y) flies'.
#pred legally_holds(_,flies(Y,X)) :: 'it legally holds that it is @(X) that @(Y) flies'.
according_to( ba__2_end,flies(A,true)) :-
bird(A).
overrules(ba__3_end,ba__2_end).
opposes( flies(A,true), flies(A,false)).
opposes( flies(A,false), flies(A,true)).
according_to( ba__3_end,flies(A,false)) :-
penguin(A).
penguin(tweety).
#pred overrules(R1,R2) :: 'the conclusion in @(R1) overrules the conclusion in @(R2)'.
#pred opposes(C1,C2) :: 'the conclusion @(C1) opposes the conclusion @(C2)'.
#pred defeated(R,_) :: 'the conclusion in @(R) is defeated'.
#pred refuted(R,_) :: 'the conclusion in @(R) is refuted'.
refuted(R,C) :-
opposes(C,OC),
overrules(OR,R),
according_to(OR,OC).
defeated(R,C) :-
refuted(R,C).
legally_holds(R,C) :-
according_to(R,C),
not defeated(R,C).
%?- scasp(legally_holds(_,flies(tweety,A)),[tree(Tree)]),with_output_to(string(Human), human_justification_tree(Tree,[])).
The code works properly if run on swish. But if you run it through SwiplServer, or at the Prolog top-level, you get a determinism error on human_justification_tree.
The response at top-level is:
?- scasp(legally_holds(_,flies(tweety,A)),[tree(Tree)]),with_output_to(string(Human), human_justification_tree(Tree,[])).
Correct to: "scasp_just_human:human_justification_tree(Tree,[])"?
Please answer 'y' or 'n'? yes
ERROR: Deterministic procedure scasp_just_human:human_justification_tree/2 failed
ERROR: In:
ERROR: [11] with_output_to(string(_19662),scasp_just_human:human_justification_tree(...,[]))
ERROR: [10] '<meta-call>'('<garbage_collected>') <foreign>
ERROR: [9] toplevel_call('<garbage_collected>') at /usr/lib/swi-prolog/boot/toplevel.pl:1162
Call: (12) modules:destroy_module('tmp-1-3739224655756611777') ? Unknown option (h for help)
Call: (12) modules:destroy_module('tmp-1-3739224655756611777') ? creep
^ Call: (13) retractall(system:'$load_context_module'(_24636, 'tmp-1-3739224655756611777', _24640)) ? creep
^ Exit: (13) retractall(system:'$load_context_module'(_24636, 'tmp-1-3739224655756611777', _24640)) ? creep
Exit: (12) modules:destroy_module('tmp-1-3739224655756611777') ? creep
?-
The query runs and behaves properly if it is just ?- scasp(legally_holds(_,flies(tweety,A))).
I’m using swipl 8.5.9 and the latest version of the s(CASP) library.