This is the file:
:- use_module(library(scasp)).
:- use_module(library(scasp/human)).
:- use_module(library(scasp/output)).
:- meta_predicate
blawxrun(0,-).
blawxrun(Query, Human) :-
scasp(Query,[tree(Tree)]),
ovar_analyze_term(t(A, Tree),[name_constraints(true)]), ovar_analyze_term(t(B, Tree),[name_constraints(true)]),
with_output_to(string(Human),
human_justification_tree(Tree,[])).
#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).
#pred game(X) :: '@(X) is a game'.
#pred player(X) :: '@(X) is a player'.
#pred player(Y,X) :: '@(X) played in @(Y)'.
#pred sign(X) :: '@(X) is a sign'.
sign(rock).
sign(paper).
sign(scissors).
beats(rock,scissors).
#pred beats(X,Y) :: '@(X) beats @(Y)'.
beats(paper,rock).
beats(scissors,paper).
#pred winner(X,Y) :: 'the winner of @(X) is @(Y)'.
#pred throw(X,Y) :: '@(X) threw @(Y)'.
winner(Game,Player1) :-
player(Game,Player1),
player(Game,Player2),
throw(Player1,Throw1),
throw(Player2,Throw2),
beats(Throw1,Throw2).
#abducible player(B,A).
#abducible throw(A,B).
The query is blawxrun(winner(A,B),Human).
It succeeds at top level, but fails with a determinism error on html_justification_tree
if you turn on debug. I’m not sure what to make of that, but that doesn’t seem to be the problem I’m currently fighting.
I then ran MQI in standalone as suggested in the docs using mqi_start([port(5000),password('test")]).
and running the debug commands.
Then I ran the code above with the following python:
rules = """
... (as above)
"""
rulefile = tempfile.NamedTemporaryFile('w',delete=False)
rulefile.write(rules)
rulefile.close()
rulefilename = rulefile.name
try:
with PrologMQI(launch_mqi=False, port=5000, password="test") as swipl:
with swipl.create_thread() as swipl_thread:
load_file_answer = swipl_thread.query("['" + rulefilename + "'].")
query_answer = swipl_thread.query("blawxrun(winner(A,B),Human).")
print(query_answer)
except PrologError as err:
print(err)
In the output I see the following error:
% [Thread mqi2_conn2_comm] Session finished. Communication thread exception: error(type_error(free_of_attvar,true( ... ),context(system:numbervars/4,_6164))
% [Thread mqi2_conn2_comm] Attempting to abort thread: mqi2_conn2_goal. thread_signal_exception: _6306
% [Thread mqi2_conn2_goal] Thread mqi2_conn2_goal exited with status exception($aborted)
% [Thread mqi2_conn2_comm] Ending session mqi2_conn2_comm
% [Thread mqi2_conn2_comm] Thread mqi2_conn2_comm exited with status true
% [Thread mqi2_conn2_comm] Expected thread status, detaching thread mqi2_conn2_comm
where ...
is the (long) content of the query response.
free_of_attvar
reminds me that if you run the code at top level, you get the following put_attr
lines at the end of the output…
?- blawxrun(winner(A,B),Human).
Human = " the winner of A is B, because\n B played in A, because\n there is no evidence that o_player holds for A, and B, because\n it is assumed that B played in A\n abducible$ holds for player(_18200,_18218), because\n there is no evidence that abducible$$ holds for player(_18200,_18218), because\n abducible$ holds for player(_18200,_18218), because\n it is assumed that there is no evidence that abducible$$ holds for player(_18200,_18218)\n C played in A, because\n there is no evidence that o_player holds for A, and C, because\n it is assumed that C played in A\n abducible$ holds for player(_18200,_18236), because\n there is no evidence that abducible$$ holds for player(_18200,_18236), because\n abducible$ holds for player(_18200,_18236), because\n it is assumed that there is no evidence that abducible$$ holds for player(_18200,_18236)\n B threw rock, because\n there is no evidence that o_throw holds for B, and rock, because\n it is assumed that B threw rock\n abducible$ holds for throw(_18218,rock), because\n there is no evidence that abducible$$ holds for throw(_18218,rock), because\n abducible$ holds for throw(_18218,rock), because\n it is assumed that there is no evidence that abducible$$ holds for throw(_18218,rock)\n C threw scissors, because\n there is no evidence that o_throw holds for C, and scissors, because\n it is assumed that C threw scissors\n abducible$ holds for throw(_18236,scissors), because\n there is no evidence that abducible$$ holds for throw(_18236,scissors), because\n abducible$ holds for throw(_18236,scissors), because\n it is assumed that there is no evidence that abducible$$ holds for throw(_18236,scissors)\n rock beats scissors\n ∎\n",
% s(CASP) model
{ beats(rock,scissors), not o_throw(_A,scissors), throw(_A,scissors),
not o_player(A,B), player(A,B), winner(A,B),
not o_player(A,_A), player(A,_A),
not o_throw(B,rock), throw(B,rock)
},
% s(CASP) justification
query ←
winner(A,B) ←
player(A,B) ←
not o_player(A,B) ←
chs(player(A,B)) ∧
'abducible$'(player(A,B)) ←
not 'abducible$$'(player(A,B)) ←
'abducible$'(player(A,B)) ←
chs(not 'abducible$$'(player(A,B))) ∧
player(A,_A) ←
not o_player(A,_A) ←
chs(player(A,_A)) ∧
'abducible$'(player(A,_A)) ←
not 'abducible$$'(player(A,_A)) ←
'abducible$'(player(A,_A)) ←
chs(not 'abducible$$'(player(A,_A))) ∧
throw(B,rock) ←
not o_throw(B,rock) ←
chs(throw(B,rock)) ∧
'abducible$'(throw(B,rock)) ←
not 'abducible$$'(throw(B,rock)) ←
'abducible$'(throw(B,rock)) ←
chs(not 'abducible$$'(throw(B,rock))) ∧
throw(_A,scissors) ←
not o_throw(_A,scissors) ←
chs(throw(_A,scissors)) ∧
'abducible$'(throw(_A,scissors)) ←
not 'abducible$$'(throw(_A,scissors)) ←
'abducible$'(throw(_A,scissors)) ←
chs(not 'abducible$$'(throw(_A,scissors))) ∧
beats(rock,scissors),
put_attr(A, scasp_output, name('A')),
put_attr(B, scasp_output, name('B')),
put_attr(_A, scasp_output, name('C'))
The put_attr
lines do not occur if you omit the ovar_analyze_term
line from the definition of blawxrun
.
So working theory:
- MQI is gracelessly terminating the connection when the type error is detected without advising the client, and
- Either or both of:
(a) MQI is failing to deal with information in the results that belongs, or,
(b) ovar_analyze_term
is adding information to the results that shouldn’t be there.
- There may be a determinism problem with
html_justification_tree
.
If I can figure out how to troubleshoot further, I will. Thanks for the help.