-
I have the following prolog file: :- use_module(library(clpz)).
:- use_module(library(tabling)).
:- use_module(library(debug)).
:- dynamic(memo_/1).
memo(Goal) :-
( memo_(Goal)
-> true
; once(Goal),
assertz(memo_(Goal))
).
foo_memo(0, _, 1).
foo_memo(N, X, Y) :-
N1 #= N - 1,
memo(foo_memo(N1, X, Y)).
:- table foo/3.
foo(0, _, 1).
foo(N, X, Y) :-
N1 #= N - 1,
$ foo(N1, X, Y). where the Once the file is consulted, the query
However the seemingly equivalent ?- foo(2, 125, X).
call:user:foo(1,125,A).
call:user:foo(0,125,A).
call:user:foo(-1,125,A).
call:user:foo(-2,125,A).
call:user:foo(-3,125,A).
call:user:foo(-4,125,A).
...
call:user:foo(-424,125,A).
exception:error('$interrupt_thrown',repl/0):user:foo(-424,125,A).
exit:user:foo(0,125,1).
exit:user:foo(1,125,1).
X = 1
; ... .
?- foo(2, 125, X).
X = 1
; ... . If I alter the first clause a bit with a cut, the query becomes instant too: :- table foo/3.
foo(0, _, 1) :- !.
foo(N, X, Y) :-
N1 #= N - 1,
$ foo(N1, X, Y). then: ?- foo(2, 125, X).
call:user:foo(1,125,A).
call:user:foo(0,125,A).
exit:user:foo(0,125,1).
exit:user:foo(1,125,1).
X = 1 Why is this the case? I would have expected the first clause to be successful, then the query to return, not to explore other branches without providing an answer first. |
Beta Was this translation helpful? Give feedback.
Replies: 5 comments 7 replies
-
Is this true even if you remove the |
Beta Was this translation helpful? Give feedback.
-
This does seem to be the same on SWI-Prolog. With the file: :- table foo/3.
foo(0, _, 1).
foo(N, X, Y) :-
N1 is N - 1,
foo(N1, X, Y). I get the following trace:
I see an |
Beta Was this translation helpful? Give feedback.
-
This is really fascinating. ?- foo(2, 125, X).
call:user:foo(1,125,A).
call:user:foo(0,125,A).
call:user:foo(-1,125,A).
call:user:foo(-2,125,A).
call:user:foo(-3,125,A).
call:user:foo(-4,125,A). Your finding here shows that the SLG resolution of tabling does not meet our standard intuition for how SLD resolution works. It never seems to hit the "base case" on the first pass, but it is "tabled" for the second pass. |
Beta Was this translation helpful? Give feedback.
-
I think the second clause misses a constraint Without this constraint, the predicate does not terminate universally, whether or not we use tabling: ?- foo(2, 125, X), false. loops. |
Beta Was this translation helpful? Give feedback.
-
I think I found the why for this phenomenon. The paper on which tabling is based mentions the following:
With figure 4 being: run_leader(Wrapper,Worker,Table) :-
create_scheduling_component,
activate(Wrapper,Worker,Table),
completion,
unset_scheduling_component. And then:
as seen in figure 6: activate(Wrapper,Worker,Table) :-
table_set_status(Table,active),
(
delim(Wrapper,Worker,Table),
fail
;
true
). So indeed it will run the predicate and for this to terminate it has to terminate universally, as @triska pointed out above. If you agree with my conclusion, let's mark this as the solution to the discussion (although I found it thanks to Markus' suggestion!). |
Beta Was this translation helpful? Give feedback.
I think I found the why for this phenomenon. The paper on which tabling is based mentions the following:
With figure 4 being:
And then:
as seen in figure 6:
So indeed it will run the predicate and for this to …