Hi! In the code below you can find some simple predicates I created, that exhibit a surprising behavior.
The main predicate, explainSuccess is a simple debugging tool I’m writing to check out swipl introspection capabilities. If you pass explainSuccess a goal that succeeds, it will show you the instantiations of the variables.
I have several question on how I could improve this, but the first one is: at the bottom of the file I included two queries: one calls goal, and succeeds, the other calls (goal, true) and fails 
could someone explain how that’s possible? Is that because I’m using trace in the definition of the explainSuccess predicate?
:- use_module(library(clpfd)).
:- use_module(library(dcg/basics)).
:- use_module('reif.pl').
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% A simple explanation mechanism:
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
prolog_trace_interception(exit, Frame, _PC, continue) :-
prolog_frame_attribute(Frame, level, Level),
(
(Level = 11)
-> (prolog_frame_attribute(Frame, goal, Goal),
assertz(debugging_info(clause(Goal))))
; (Level = 12)
-> (prolog_frame_attribute(Frame, goal, Goal),
assertz(debugging_info(subclause(Goal))))
; true
).
prolog_trace_interception(_Port, _Frame, _PC, continue).
reconstruct(Out) :-
debugging_info(clause(Clause)),
findall(Subclause, debugging_info(subclause(Subclause)), Subclauses),
Out = (Clause :- Subclauses).
explainSuccess(G, Out) :-
trace,
call(G),
notrace,
reconstruct(Out),
abolish(debugging_info/1).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% A simple predicate to test:
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
zip([], [], []).
zip(As, [], []) :- dif(As, []).
zip([], Bs, []) :- dif(Bs, []).
zip([A|As], [B|Bs], [A-B|ABs]) :-
zip(As,Bs,ABs).
enumerate(As, Enumerated) :-
length(As, L),
numlist(1,L,Ns),
zip(As, Ns, Enumerated).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% The problem I described in the topic
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%?- explainSuccess(enumerate([a,b,c,d], X), Out).
%@ X = [a-1, b-2, c-3, d-4],
%@ Out = (enumerate([a, b, c, d], [a-1, b-2, c-3, d-4]):-[system:length([a, b, c, d], 4), lists:numlist(1, 4, [1, 2, 3, 4]), zip([a, b, c, d], [1, 2, 3, 4], [a-1, b-2, c-3, ... - ...])]) ;
%@ false.
%?- explainSuccess(enumerate([a,b,c,d], X), Out), true.
%@ false.
